LicenceBox.st
author Claus Gittinger <cg@exept.de>
Tue, 09 Mar 1999 23:34:03 +0100
changeset 1243 e955dcfe26a2
parent 1242 dcaf3fb826da
child 1266 20df0cbfaf95
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1996 by eXept Software AG
	      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.
"

DialogBox subclass:#LicenceBox
	instanceVariableNames:'accepted destroySemaphore fileName'
	classVariableNames:'LicenceRejectSignal'
	poolDictionaries:''
	category:'Views-DialogBoxes'
!

!LicenceBox class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1996 by eXept Software AG
	      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
"
    LicenceBox shows a licence text when opened, an returns true,
    if the licence has been accepted, false otherwise.

    [author:]
	Stefan Vogel

    [see also:]
	AboutBox
"
!

examples
"
						[exBegin]
    LicenceRejectSignal handle:[:ex|
	Transcript showCR:'Licence rejected'.
    ] do:[
	LicenceBox open.
	Transcript showCR:'Licence accepted'.
    ] 
						[exEnd]
"
! !

!LicenceBox class methodsFor:'initialization'!

initialize
    LicenceRejectSignal isNil ifTrue:[
	LicenceRejectSignal := ErrorSignal newSignalMayProceed:true.
	LicenceRejectSignal nameClass:self message:#licenceRejectSignal.
	LicenceRejectSignal notifierString:'licence rejected by user'.
    ].

    "
     self initialize
    "
! !

!LicenceBox class methodsFor:'instance creation'!

open
    "open myself modal and return true if accepted, false otherwise"

    ^ super open accepted.

    "
     LicenceBox open
    "

    "Modified: 9.9.1996 / 17:52:48 / stefan"
! !

!LicenceBox class methodsFor:'Signal constants'!

licenceRejectSignal
    "licence has been rejected by user"

    ^ LicenceRejectSignal

! !

!LicenceBox methodsFor:'accessing'!

accepted
    "return accepted"

    ^ accepted

    "Created: 6.9.1996 / 13:24:44 / stefan"
!

accepted:something
    "set accepted"

    accepted := something.

    "Created: 6.9.1996 / 13:24:44 / stefan"
! !

!LicenceBox methodsFor:'destroying'!

terminate
    "this is the close from a windowmanager
     (only if UseTransientViews == true).
     Redefined, since ModalBox keeps the View alive (only hidden)"

    self destroy.

    "Created: 9.9.1996 / 15:15:31 / stefan"
! !

!LicenceBox methodsFor:'initialization'!

initialize    
    |textView smallScreen nLines|

    super initialize.

    (Display height < 800) ifTrue:[
	(Display height < 500) ifTrue:[
	    nLines := 20
	] ifFalse:[
	    nLines := 30
	]
    ] ifFalse:[
	nLines := 40
    ].

    accepted := false.

    (self addTextLabel:(resources string:'Please read the licence terms:')) adjust:#left.
    textView := self addTextBoxOn:nil 
			class:HTMLDocumentView
			withNumberOfLines:nLines
			hScrollable:true 
			vScrollable:true.

    self width:(textView preferredExtentForLines:nLines cols:70) x.
    textView setText:(self licenceText).
    textView setTopDirectoryName:(self topDirectory).
    self addAbortButtonLabelled:(resources string:'reject licence terms').
    self addOkButtonLabelled:(resources string:'accept licence terms').
    self abortAction:[self destroy. accepted := false. LicenceRejectSignal raise].
    self okAction:[self destroy. accepted := true].
    self stickAtBottomWithVariableHeight:textView.

    "Modified: 9.9.1996 / 17:52:13 / stefan"
! !

!LicenceBox methodsFor:'private'!

licenceFile
    "get filename of licence file"

    |fn sysFile|

    fileName isNil ifTrue:[
	fileName := fn := resources at:'LICENCEFILE' default:nil.
	fileName isNil ifTrue:[
	    Smalltalk releaseIdentification = 'ST/X_free_demo_vsn' ifTrue:[
		fn := 'doc/online/english/LICENCE_DEMO_STX.html'.
	    ] ifFalse:[
		fn := 'doc/online/english/LICENCE_STX.html'.
	    ].
	    fileName := fn.
	].

	fileName asFilename exists ifFalse:[
	    fileName := Smalltalk getSystemFileName:fileName.
	    fileName isNil ifTrue:[
		fileName := '../../' , fn.
		fileName asFilename exists ifFalse:[
		    fileName := Smalltalk getSystemFileName:'doc/online/german/LICENCE_STX.html'.
		    fileName isNil ifTrue:[
			fileName := '../../doc/online/german/LICENCE_STX.html'.
		    ]
		].
	    ].
	].
	fileName asFilename exists ifFalse:[
	    fileName := nil
	].
    ].
    ^ fileName 

    "
     LicenceBox new licenceFile
    "

    "Modified: / 23.4.1998 / 11:40:25 / cg"
!

licenceText
    "get licence text"

    |file|

    file := self licenceFile.
    file isNil ifTrue:[
	^ 'oops - you are not allowed to remove the LICENSE file !!'
    ].
    ^ file asFilename contents.

    "
     LicenceBox new licenceText
    "

!

topDirectory
    "get name of top directory"

    |file|

    file := self licenceFile.
    file isNil ifTrue:[
	^ ''
    ].
    ^ file asFilename directoryName.

    "
     LicenceBox new topDirectory
    "

! !

!LicenceBox class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/LicenceBox.st,v 1.12 1999-03-09 22:34:03 cg Exp $'
! !
LicenceBox initialize!