MeasurementValue.st
author Claus Gittinger <cg@exept.de>
Sat, 28 Feb 2009 12:52:06 +0100
changeset 11607 39bd3dc180df
parent 11606 f657ce220093
child 11717 62d715950754
permissions -rw-r--r--
comment

"
 COPYRIGHT (c) 2007 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.
"
"{ Package: 'stx:libbasic' }"

Number subclass:#MeasurementValue
	instanceVariableNames:'value minValue maxValue'
	classVariableNames:'MeasurementValueZero'
	poolDictionaries:''
	category:'Magnitude-Numbers'
!

!MeasurementValue class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2007 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
"
    A MeasurementValue is a numeric value with an error, such as returned
    by measurement devices (Volt-Meter). For example, if a measurement-device has
    an error of 10%, a measured value of 20 could be any value between 18 and 22.

    Arithmetic operations keep track of the error; if any operand is a MeasurementValue,
    the operation returns a MeasurementValue as result.

    This class is possibly unfinished and needs more arithmetic methods.
    For now, the stuff found here represents our needs and more might be added in the future.

    Also notice, that instances do not keep the error as a fraction, but instead a min. and maxValue.
    That means, that we can handle the case where the error is different in
    the positive and negative directions.
    I am not sure if this is more flexibility than needed in the long run.

    [author:]
        Claus Gittinger

    [see also:]
        Number
        Float ShortFloat Fraction FixedPoint Integer Complex
        FloatArray DoubleArray
"
!

examples
"
    Notice, how the errors accumulate...
                                                                        [exBegin]
    |voltage current power|

    voltage := MeasurementValue value:10 error:0.05.
    current := MeasurementValue value:2 error:0.1.
    power := voltage * current.
    power.                   
    power minValue.
    power maxValue.
                                                                        [exEnd]

                                                                        [exBegin]
    |voltage current power|

    voltage := MeasurementValue value:10 error:0.05.
    current := 2.
    power := voltage * current.
    power
                                                                        [exEnd]

                                                                        [exBegin]
    |voltage doubleVoltage|

    voltage := MeasurementValue value:10 error:0.1.
    doubleVoltage := 2 * voltage.
    doubleVoltage
                                                                        [exEnd]
"
! !

!MeasurementValue class methodsFor:'instance creation'!

value:arg1 error:arg2
    "return a new measurementValue with a given value and an error (fraction)"

    ^ self new value:arg1 error:arg2

    "
     MeasurementValue value:10 error:0.2 
    "
!

value:arg1 minValue:arg2 maxValue:arg3
    "return a new measurementValue with a given value and an error given as min-max values.
     Use this, if the error is not the same in both directions"

    ^ self new value:arg1 minValue:arg2 maxValue:arg3

    "a power of 10 error:
     MeasurementValue value:5 minValue:1 maxValue:10   
    "
! !

!MeasurementValue class methodsFor:'constants'!

unity
    "return the neutral element for multiplication"

    ^ 1

    "
     self unity
    "
!

zero
    "return the neutral element for addition (0 +/- 0)"

    MeasurementValueZero isNil ifTrue:[
        MeasurementValueZero := self value:0 minValue:0 maxValue:0
    ].
    ^ MeasurementValueZero

    "
     self zero
    "
! !

!MeasurementValue methodsFor:'accessing'!

maxValue
    "the maximum possible value, considerung what has been measured and what the measurement error is"

    ^ maxValue
!

minValue
    "the minimum possible value, considerung what has been measured and what the measurement error is"

    ^ minValue
!

value
    "the measured value"

    ^ value
! !

!MeasurementValue methodsFor:'arithmetic'!

* aNumber
    ^ MeasurementValue new
        value:(value * aNumber value)
        minValue:(minValue * aNumber minValue)
        maxValue:(maxValue * aNumber maxValue)
!

+ aNumber
    ^ MeasurementValue new
        value:(value + aNumber value)
        minValue:(minValue + aNumber minValue)
        maxValue:(maxValue + aNumber maxValue)
!

- aNumber
    ^ MeasurementValue new
        value:(value - aNumber value)
        minValue:(minValue - aNumber maxValue)
        maxValue:(maxValue - aNumber minValue)
!

/ aNumber
    ^ MeasurementValue new
        value:(value / aNumber value)
        minValue:(minValue / aNumber maxValue)
        maxValue:(maxValue / aNumber minValue)
! !

!MeasurementValue methodsFor:'coercing & converting'!

+/- error
    "return a MeasurementValue with the given error."

    "/ what should I do here - take the new error,
    "/ or multiply them ????
    self error.

    minValue := value - error.
    maxValue := value + error.
!

coerce:aNumber
    ^ MeasurementValue value:aNumber minValue:aNumber maxValue:aNumber
        
!

generality
    "/ adding 1 has the subtle side effect of enforcing a call to cuerce:
    "/ for mixed type operaions (i.e. Int * MeasurementValue).
    "/ try it.

    ^ value generality + 1 
! !

!MeasurementValue methodsFor:'comparing'!

< aNumber
    ^ maxValue < aNumber
!

= aNumber
    "hard to tell, what we want here..."

    ^ value = aNumber value
    and:[ minValue = aNumber minValue
    and:[ maxValue = aNumber maxValue ]]
!

lessFromFloat:aFloat
    "aFloat < self ?"

    ^ aFloat < minValue
!

lessFromInteger:anInteger
    "anInteger < self ?"

    ^ anInteger < minValue
! !

!MeasurementValue methodsFor:'printing & storing'!

printOn:aStream
    aStream nextPutAll:'('.
    (maxValue-value) = (value-minValue) ifTrue:[
        value storeOn:aStream.
        aStream nextPutAll:' +/- '.
        (maxValue-value) storeOn:aStream
    ] ifFalse:[
        aStream nextPutAll:'MeasurementValue value:'.
        value storeOn:aStream.
        aStream nextPutAll:' minValue:'.
        minValue storeOn:aStream.
        aStream nextPutAll:' maxValue:'.
        maxValue storeOn:aStream.
    ].
    ')' printOn:aStream.

    "
     (5 +/- 1) storeString 
     (MeasurementValue value:5 minValue:3 maxValue:8) storeString 
    "
! !

!MeasurementValue methodsFor:'private accessing'!

value:valueArg error:errorFraction 
    self 
        value:valueArg
        minValue:(valueArg * (1-errorFraction))
        maxValue:(valueArg * (1+errorFraction)). 
!

value:valueArg minValue:minValueArg maxValue:maxValueArg 
    value := valueArg.
    minValue := minValueArg.
    maxValue := maxValueArg.
! !

!MeasurementValue methodsFor:'testing'!

between:min and:max
    minValue < min ifTrue:[^ false].
    maxValue > max ifTrue:[^ false].
    ^ true
! !

!MeasurementValue class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/MeasurementValue.st,v 1.8 2009-02-28 11:52:06 cg Exp $'
! !