UnitConverter.st
author Claus Gittinger <cg@exept.de>
Thu, 09 Jan 2003 18:16:59 +0100
changeset 1135 9a343ebe206b
parent 1132 2f0305cb691b
child 1143 ad4a5f867538
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1996 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:libbasic2' }"

Object subclass:#UnitConverter
	instanceVariableNames:''
	classVariableNames:'Conversions Scaling Aliases Constants'
	poolDictionaries:''
	category:'Magnitude-General'
!

!UnitConverter class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1996 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
"
    In order to collect various unit conversions into one central
    manageable (and especially: browsable) place, all previously
    spread knowledge about metric (and other) conversions has been
    brought into this class.

    This class is purely functional, abstract and has no instances;
    all queries are via class protocol.
    Choosing the Magnitudes category as its home is arbitrary.

    The supported units are setup in the classes initialize method;
    supported are:
        meter - inch - feet - foot - yard
        meter2 - acre - 'german-ar' 'german-hektar' are
        liter - gallon - barrel - floz
        celsius - fahrenheit
    and many others.

    The converter does a recursive search for a conversion;
    thus, if there is a conversion from #inch to #millimeter and another 
    from #millimeter to #kilometer, conversion from #inch to #kilometer
    is found automatically.

    No Warranty:
        The numbers and conversion factors were obtained from the Unix
        units command. Please check before using it - there might be
        typos or wrong conversions in the setup code.


    [author:]
        Claus Gittinger

    see also:
        examples
        /usr/share/lib/unittab (if present on your system)
"
!

examples
"
    ever wanted to know, how many floz's are there in a european
    Coce bottle ?
                                                                [exBegin]
        Transcript showCR:
            (UnitConverter convert:1 from:#liter to:#floz)
                                                                [exEnd]

                                                                [exBegin]
        Transcript showCR:
            (UnitConverter convert:43.5 from:#oz to:#gram)
                                                                [exEnd]

    or, how many square-meters an acre is:
                                                                [exBegin]
        Transcript showCR:
            (UnitConverter convert:1 from:#acre to:#'meter^2')
                                                                [exEnd]


    or europeans might want to know, what those
    fahrenheit numbers mean in an US weather report ;-):
                                                                [exBegin]
        Transcript showCR:(
            (UnitConverter convert:80 from:#fahrenheit to:#celsius)
                asFixedPoint:1)
                                                                [exEnd]


    how fast do I drive ? :-)
                                                                [exBegin]
        Transcript showCR:(
                UnitConverter convert:200 from:#'km/hr' to:#'mile/hr')
                                                                [exEnd]
    how fast does Chris drive ? :-)
                                                                [exBegin]
        Transcript showCR:(
                UnitConverter convert:65 from:#'mile/hr' to:#'km/hr')
                                                                [exEnd]


    calories or joule ?
                                                                [exBegin]
        Transcript showCR:(
                UnitConverter convert:0.18 from:#'kilocalorie' to:#'kilojoule')
                                                                [exEnd]
                                                                [exBegin]
        Transcript showCR:(
                UnitConverter convert:2000 from:#'kilocalorie' to:#'kilojoule')
                                                                [exEnd]


    distances:
        
                                                                [exBegin]
        Transcript showCR:(
            UnitConverter convert:1 from:#'lightsecond' to:#'kilometer') 
                                                                [exEnd]
    thats the same:
                                                                [exBegin]
        Transcript showCR:(
            UnitConverter convert:1 from:#'lightspeed*s' to:#'kilometer') 
                                                                [exEnd]
    a days travel ...
                                                                [exBegin]
        Transcript showCR:(
            UnitConverter convert:1 from:#'lightspeed*dy' to:#'kilometer') 
                                                                [exEnd]
    a year travel ...
                                                                [exBegin]
        Transcript showCR:(
            UnitConverter convert:1 from:#'lightyear' to:#'kilometer') 
                                                                [exEnd]


    real estate buyers might want to know, how many acres
    a german ar is:
                                                                [exBegin]
        Transcript showCR:
            (UnitConverter convert:1 from:#'german-ar' to:#acre)
                                                                [exEnd]
    - or how many square-feet are there in your living room:
                                                                [exBegin]
        Transcript showCR:
            (UnitConverter convert:100 from:#'meter^2' to:#'foot^2')   
                                                                [exEnd]
    - or how about:
                                                                [exBegin]
        Transcript showCR:
            (UnitConverter convert:3600 from:#'ft*ft' to:#'m*,')   
                                                                [exEnd]


    how many tea spoons are there in a cubic meter ?
    (roughly, since a teaspoon is not a standard unit)
                                                                [exBegin]
        Transcript showCR:
            (UnitConverter convert:1 from:#'meter^3' to:#teaspoon)
                                                                [exEnd]
    how wide is a US page in inches:
                                                                [exBegin]
        Transcript showCR:
            (UnitConverter convert:1 from:#'letterW' to:#inch)   
                                                                [exEnd]
    - in millimeter:
                                                                [exBegin]
        Transcript showCR:
            (UnitConverter convert:1 from:#'letterW' to:#mm)   
                                                                [exEnd]


    the height of a US page in inches:
                                                                [exBegin]
        Transcript showCR:
            (UnitConverter convert:1 from:#'letterH' to:#inch)   
                                                                [exEnd]
    - in millimeter:
                                                                [exBegin]
        Transcript showCR:
            (UnitConverter convert:1 from:#'letterH' to:#mm)   
                                                                [exEnd]


    the same for european A4 standard page:
                                                                [exBegin]
        Transcript showCR:
            (UnitConverter convert:1 from:#'a4H' to:#mm)   
                                                                [exEnd]
                                                                [exBegin]
        Transcript showCR:
            (UnitConverter convert:1 from:#'a4H' to:#inch)   
                                                                [exEnd]
"
! !

!UnitConverter class methodsFor:'initialization'!

initializeConversions
    "initialize common conversions"

    self initializeScaleFactors.

    Conversions := IdentityDictionary new.
    Aliases := IdentityDictionary new.
    Constants := IdentityDictionary new.

    "/ ---------- velocity -------------

    Constants at:#lightspeed   put:#(2.997925E8   #'m/s').


    "/ -------------- length -------------

    Aliases at:#km       put:#kilometer.
    Aliases at:#m        put:#meter.
    Aliases at:#dm       put:#decimeter.
    Aliases at:#cm       put:#centimeter.
    Aliases at:#mm       put:#millimeter.
    Aliases at:#micron   put:#micrometer.
    Aliases at:#nm       put:#nanometer.
    Aliases at:#angstrom put:#decinanometer.

    "/ US
    self addConversion:12       from:#foot to:#inch.
    self addConversion:3        from:#yard to:#foot.
    self addConversion:5280     from:#mile to:#foot.
    self addConversion:0.001    from:#inch to:#mil.

    Aliases at:#feet put:#foot.
    Aliases at:#ft   put:#foot.
    Aliases at:#yd   put:#yard.
    Aliases at:#mi   put:#mile.

    "/ inch to millimeter
    self addConversion:(25.4/1000) from:#inch to:#meter.

    "/ nautic
    self addConversion:1852        from:#'nautical-mile' to:#meter.

    Aliases at:#lightsecond put:#'lightspeed*s'.
    Aliases at:#lightyear   put:#'lightspeed*yr'.

    self addConversion:((Constants at:#lightspeed) at:1) from:#'lightspeed*s' to:#'meter'.

    "/ ---------- time -------------

    self addConversion:60           from:#min to:#s.
    self addConversion:60           from:#hr  to:#min.
    self addConversion:24           from:#dy  to:#hr.
    self addConversion:365.24219879 from:#yr  to:#dy.


    "/ ---------- printing -------------
    self initializePrintValues.

    "/ ---------------- area -------------------

    "/ US
    self addConversion:4840        from:#acre  to:#'yard^2'.

    self addConversion:100         from:#are      to:#'meter^2'.
    self addConversion:100         from:#hectare  to:#are.

    "/ german area - add your countries, and return to me ...
    Aliases at:#'german-ar'      put:#are.
    Aliases at:#'german-hektar'  put:#hectare.


    "/ ---------------- liquid ---------------- 

    self addConversion:231      from:#gallon to:#'inch^3'.
    self addConversion:(1/4)    from:#quart to:#gallon.  "/ well - at least here,
                                                         "/ thats also 1/4th of a good wine ;-)
    self addConversion:(1/2)    from:#pint to:#quart.
    self addConversion:(1/16)   from:#floz to:#pint.
    self addConversion:(1/8)    from:#fldr to:#floz.

    self addConversion:42       from:#barrel to:#gallon.
    self addConversion:35.23907 from:#bushel to:#liter.

    Aliases at:#cc    put:#'cm^3'.
    Aliases at:#liter put:#kilocc.
    Aliases at:#ml    put:#milliliter.
    Aliases at:#gal   put:#gallon.
    Aliases at:#qt    put:#quart.


    "/ ---------------- mass ---------------- 

    self addConversion:28.35     from:#ounce to:#gram.
    self addConversion:453.59237 from:#lb    to:#gram.
    self addConversion:205       from:#carat to:#milligram.

    Aliases at:#oz put:#ounce.
    Aliases at:#lbs put:#lb.

    Aliases at:#gm put:#gram.
    Aliases at:#kg put:#kilogram.

    "/ well, a pint of beer is not always:
    self addConversion:277.420 from:#'british-gallon'  to:#'inch^3'.
    self addConversion:(1/4)   from:#'british-quart'   to:#'british-gallon'.
    self addConversion:(1/2)   from:#'british-pint'    to:#'british-quart'.
    self addConversion:(1/16)  from:#'british-floz'    to:#'british-pint'.

    "/ ---------------- energy ---------------- 

    Aliases at:#cal     put:#calorie.
    Aliases at:#nt      put:#newton.
    Aliases at:#joule   put:#'nt*m'.

    self addConversion:4.1868 from:#calorie  to:#joule.


    "/ ---------------- cooking ---------------- 

    self addConversion:4      from:#tablespoon   to:#fldr.
    self addConversion:(4/3)  from:#teaspoon     to:#fldr.


    "/ ---------------- temperature ---------------- 

    self addConversion:[:d | d * 1.8 + 32] from:#celsius    to:#fahrenheit.
    self addConversion:[:f | f - 32 / 1.8] from:#fahrenheit to:#celsius.

    "
     Conversions := nil.
     UnitConverter initializeConversions
    "

    "Created: / 22.7.1997 / 13:56:40 / cg"
    "Modified: / 10.10.2001 / 14:39:04 / cg"
!

initializePrintValues
    "/ inch to (roughly) a typesetter point
    self addConversion:(1/72)      from:#point to:#inch.

    "/ point to twips; 20 twips (as in Rich-Text-Format) make a point
    self addConversion:(1/20)      from:#twip  to:#point.

    "/ US paper
    self addConversion:11          from:#'letter-page-height' to:#inch.
    self addConversion:8.5         from:#'letter-page-width'  to:#inch.
    self addConversion:8.5         from:#'letter-landscape-page-height'  to:#inch.
    self addConversion:11          from:#'letter-landscape-page-width' to:#inch.

    self addConversion:14          from:#'legal-page-height' to:#inch.
    self addConversion:8.5         from:#'legal-page-width'  to:#inch.
    self addConversion:8.5         from:#'legal-landscape-page-height'  to:#inch.
    self addConversion:14          from:#'legal-landscape-page-width' to:#inch.

    self addConversion:11          from:#'ledger-page-height' to:#inch.
    self addConversion:17          from:#'ledger-page-width'  to:#inch.
    self addConversion:17          from:#'ledger-landscape-page-height'  to:#inch.
    self addConversion:11          from:#'ledger-landscape-page-width' to:#inch.

    "/ European paper
    self addConversion:840         from:#'a1-page-height' to:#millimeter.
    self addConversion:592         from:#'a1-page-width'  to:#millimeter.
    self addConversion:592         from:#'a1-landscape-page-height' to:#millimeter.
    self addConversion:840         from:#'a1-landscape-page-width'  to:#millimeter.

    self addConversion:592         from:#'a2-page-height' to:#millimeter.
    self addConversion:420         from:#'a2-page-width'  to:#millimeter.
    self addConversion:420         from:#'a2-landscape-page-height' to:#millimeter.
    self addConversion:592         from:#'a2-landscape-page-width'  to:#millimeter.

    self addConversion:420         from:#'a3-page-height' to:#millimeter.
    self addConversion:296         from:#'a3-page-width'  to:#millimeter.
    self addConversion:296         from:#'a3-landscape-page-height' to:#millimeter.
    self addConversion:420         from:#'a3-landscape-page-width'  to:#millimeter.

    self addConversion:296         from:#'a4-page-height' to:#millimeter.
    self addConversion:210         from:#'a4-page-width'  to:#millimeter.
    self addConversion:210         from:#'a4-landscape-page-height' to:#millimeter.
    self addConversion:296         from:#'a4-landscape-page-width'  to:#millimeter.

    self addConversion:210         from:#'a5-page-height' to:#millimeter.
    self addConversion:148         from:#'a5-page-width'  to:#millimeter.
    self addConversion:148         from:#'a5-landscape-page-height' to:#millimeter.
    self addConversion:210         from:#'a5-landscape-page-width'  to:#millimeter.

    self addConversion:148         from:#'a6-page-height' to:#millimeter.
    self addConversion:105         from:#'a6-page-width'  to:#millimeter.
    self addConversion:105         from:#'a6-landscape-page-height' to:#millimeter.
    self addConversion:148         from:#'a6-landscape-page-width'  to:#millimeter.

    self addConversion:257         from:#'b5-page-height' to:#millimeter.
    self addConversion:182         from:#'b5-page-width'  to:#millimeter.
    self addConversion:182         from:#'b5-landscape-page-height' to:#millimeter.
    self addConversion:257         from:#'b5-landscape-page-width'  to:#millimeter.


    Aliases at:#letterW    put:#'letter-page-width'.
    Aliases at:#letterH    put:#'letter-page-height'.
    Aliases at:#legalW     put:#'legal-page-width'.
    Aliases at:#legalH     put:#'legal-page-height'.
    Aliases at:#ledgerW    put:#'ledger-page-width'.
    Aliases at:#ledgerH    put:#'ledger-page-height'.
    Aliases at:#a1W        put:#'a1-page-width'.
    Aliases at:#a1H        put:#'a1-page-height'.
    Aliases at:#a2W        put:#'a2-page-width'.
    Aliases at:#a2H        put:#'a2-page-height'.
    Aliases at:#a3W        put:#'a3-page-width'.
    Aliases at:#a3H        put:#'a3-page-height'.
    Aliases at:#a4W        put:#'a4-page-width'.
    Aliases at:#a4H        put:#'a4-page-height'.
    Aliases at:#a5W        put:#'a5-page-width'.
    Aliases at:#a5H        put:#'a5-page-height'.
    Aliases at:#a6W        put:#'a6-page-width'.
    Aliases at:#a6H        put:#'a6-page-height'.
    Aliases at:#b5W        put:#'b5-page-width'.
    Aliases at:#b5H        put:#'b5-page-height'.

    Aliases at:#letterlW   put:#'letter-landscape-page-width'.
    Aliases at:#letterlH   put:#'letter-landscape-page-height'.
    Aliases at:#legallW    put:#'legal-landscape-page-width'.
    Aliases at:#legallH    put:#'legal-landscape-page-height'.
    Aliases at:#ledgerlW   put:#'ledger-landscape-page-width'.
    Aliases at:#ledgerlH   put:#'ledger-landscape-page-height'.
    Aliases at:#a1lW       put:#'a1-landscape-page-width'.
    Aliases at:#a1lH       put:#'a1-landscape-page-height'.
    Aliases at:#a2lW       put:#'a2-landscape-page-width'.
    Aliases at:#a2lH       put:#'a2-landscape-page-height'.
    Aliases at:#a3lW       put:#'a3-landscape-page-width'.
    Aliases at:#a3lH       put:#'a3-landscape-page-height'.
    Aliases at:#a4lW       put:#'a4-landscape-page-width'.
    Aliases at:#a4lH       put:#'a4-landscape-page-height'.
    Aliases at:#a5lW       put:#'a5-landscape-page-width'.
    Aliases at:#a5lH       put:#'a5-landscape-page-height'.
    Aliases at:#a6lW       put:#'a6-landscape-page-width'.
    Aliases at:#a6lH       put:#'a6-landscape-page-height'.
    Aliases at:#b5lW       put:#'b5-landscape-page-width'.
    Aliases at:#b5lH       put:#'b5-landscape-page-height'.
!

initializeScaleFactors
    Scaling := IdentityDictionary new.

    Scaling at:#exa   put:1000000000000000000.
    Scaling at:#peta  put:1000000000000000.
    Scaling at:#tera  put:1000000000000.
    Scaling at:#giga  put:1000000000.
    Scaling at:#mega  put:1000000.
    Scaling at:#myria put:10000.
    Scaling at:#kilo  put:1000.
    Scaling at:#hecto put:100.
    Scaling at:#deci  put:(1/10).
    Scaling at:#centi put:(1/100).
    Scaling at:#milli put:(1/1000).
    Scaling at:#micro put:(1/1000000).
    Scaling at:#nano  put:(1/1000000000).
    Scaling at:#pico  put:(1/1000000000000).
    Scaling at:#femto put:(1/1000000000000000).
    Scaling at:#atto  put:(1/1000000000000000000).
! !

!UnitConverter class methodsFor:'accessing'!

scalings
    "return the set of known scaling prefixes"

    ^ Scaling keys

    "
     UnitConverter scalings
    "

    "Created: 6.8.1997 / 16:53:19 / cg"
    "Modified: 6.8.1997 / 16:58:11 / cg"
!

units
    "return the set of known units"

    |setOfUnits|

    setOfUnits := IdentitySet new.
    Conversions keysAndValuesDo:[:srcUnit :conversionInfo |
	setOfUnits add:srcUnit.
	conversionInfo keysDo:[:targetUnit |
	    setOfUnits add:targetUnit
	]
    ].
    ^ setOfUnits

    "
     UnitConverter units
    "

    "Created: 6.8.1997 / 16:57:08 / cg"
    "Modified: 6.8.1997 / 16:57:47 / cg"
! !

!UnitConverter class methodsFor:'conversions'!

convert:howMany from:sourceUnit to:destUnit
    "given a value in sourceUnit (symbolic), try to convert it
     to destUnit (symbolic); return nil, if the conversion is
     unknown."

    |u conversions alias rslt sU dU const val unit 
     i suNumerator suDenominator duNumerator duDenominator uN uD
     sF1 sF2 dF1 dF2
     s d|

"/ Transcript showCR:('try ' , sourceUnit , '->' , destUnit).

    Conversions isNil ifTrue:[
        self initializeConversions
    ].

    "/ somehow, recursion must end ...
    sourceUnit == destUnit ifTrue:[
        ^ howMany
    ].

    sourceUnit isSymbol ifFalse:[
        s := sourceUnit withoutSeparators.
        sU := s asSymbolIfInterned.
        sU notNil ifTrue:[
            ^ self convert:howMany from:sU to:destUnit
        ].
        (s startsWith:$() ifTrue:[
            (s endsWith:$)) ifTrue:[
                s := s copyFrom:2 to:(s size - 1).
                ^ self convert:howMany from:s to:destUnit
            ]
        ].
    ].
    destUnit isSymbol ifFalse:[
        d := destUnit withoutSeparators.
        dU := d asSymbolIfInterned.
        dU notNil ifTrue:[
            ^ self convert:howMany from:sourceUnit to:dU
        ].
        (d startsWith:$() ifTrue:[
            (d endsWith:$)) ifTrue:[
                d := d copyFrom:2 to:(d size - 1).
                ^ self convert:howMany from:sourceUnit to:d
            ]
        ].
    ].

    "/ first, get rid of scalers ...

    u := self unscaled:sourceUnit.
    u notNil ifTrue:[
        ^ self convert:(howMany*(u value)) from:(u key) to:destUnit
    ].

    u := self unscaled:destUnit.
    u notNil ifTrue:[
        ^ self convert:(howMany/(u value)) from:sourceUnit to:(u key)
    ].

    "/ and of aliases ...

    alias := Aliases at:sourceUnit ifAbsent:nil.
    alias notNil ifTrue:[
        ^ self convert:howMany from:alias to:destUnit
    ].
    alias := Aliases at:destUnit ifAbsent:nil.
    alias notNil ifTrue:[
        ^ self convert:howMany from:sourceUnit to:alias
    ].

    "/ any constants ?

    (Constants includesKey:sourceUnit) ifTrue:[
        const := Constants at:sourceUnit.
        val := const at:1.
        unit := const at:2.
        ^ self convert:(howMany*val) from:unit to:destUnit
    ].

    "/ compounds (^ , / or *) are very naively parsed
    "/ need a full expression parser (tree) for full power.
    "/ I leave that as an excercise to you ...


    "/ working with squares or cubics ?

    ((sourceUnit endsWith:'^2') and:[destUnit endsWith:'^2']) ifTrue:[
        sU := (sourceUnit copyWithoutLast:2) asSymbolIfInterned.
        dU := (destUnit copyWithoutLast:2) asSymbolIfInterned.
        (sU notNil and:[dU notNil]) ifTrue:[
            ^ (self convert:(howMany sqrt) from:sU to:dU) squared
        ].
        ^ self noConversionFrom:sourceUnit to:destUnit.
    ].
    ((sourceUnit endsWith:'^3') and:[destUnit endsWith:'^3']) ifTrue:[
        sU := (sourceUnit copyWithoutLast:2) asSymbolIfInterned.
        dU := (destUnit copyWithoutLast:2) asSymbolIfInterned.
        (sU notNil and:[dU notNil]) ifTrue:[
            ^ (self convert:(howMany raisedTo:(1/3)) from:sU to:dU) raisedTo:3
        ].
        ^ self noConversionFrom:sourceUnit to:destUnit.
    ].

    "/ working with fractions ?

    ((sourceUnit includes:$/) and:[destUnit includes:$/]) ifTrue:[
        "/ look for a constant conversion factor
        i := sourceUnit indexOf:$/.
        suNumerator := sourceUnit copyTo:(i - 1).
        suDenominator := sourceUnit copyFrom:(i + 1).
        i := destUnit indexOf:$/.
        duNumerator := destUnit copyTo:(i - 1).
        duDenominator := destUnit copyFrom:(i + 1).

        uN := self convert:howMany from:suNumerator to:duNumerator.
        uN notNil ifTrue:[
            uD := self convert:1 from:suDenominator to:duDenominator.
            uD notNil ifTrue:[
                ^ uN / uD
            ]
        ].
    ].

    "/ working with products ?

    ((sourceUnit includes:$*) and:[destUnit includes:$*]) ifTrue:[
        i := sourceUnit indexOf:$*.
        sF1 := sourceUnit copyTo:(i - 1).
        sF2 := sourceUnit copyFrom:(i + 1).
        i := destUnit indexOf:$*.
        dF1 := destUnit copyTo:(i - 1).
        dF2 := destUnit copyFrom:(i + 1).

        u := self convert:howMany from:sF1 to:dF1.
        u notNil ifTrue:[
            u := self convert:u from:sF2 to:dF2.
            u notNil ifTrue:[
                ^ u
            ]
        ].
    ].

    "/ the real work comes here ...

    "/ is there a direct conversion in the dataBase ?

    rslt := self convertDirect:howMany from:sourceUnit to:destUnit.
    rslt notNil ifTrue:[^ rslt].

    "/ try inverse conversion ...

    rslt := self convertDirect:1 from:destUnit to:sourceUnit.
    rslt notNil ifTrue:[ ^ howMany / rslt].

    "/ here's the deep recursion ...


    "/ try indirect conversion from source

    conversions := Conversions at:sourceUnit ifAbsent:nil.
    conversions notNil ifTrue:[
        conversions keysAndValuesDo:[:intermediateUnit :factor1 |
            |factor2|

            factor2 := self convert:factor1 from:intermediateUnit to:destUnit.
            factor2 notNil ifTrue:[^ factor2 * howMany].
        ].
    ].

    "/ try indirect conversion from dest

    conversions := Conversions at:destUnit ifAbsent:nil.
    conversions notNil ifTrue:[
        conversions keysAndValuesDo:[:intermediateUnit :factor1 |
            |factor2|

            factor2 := self convert:(factor1) from:intermediateUnit to:sourceUnit.
            factor2 notNil ifTrue:[^ howMany / factor2].
        ].
    ].

    "/ if working with a product, try each component

    (sourceUnit includes:$*) ifTrue:[
        i := sourceUnit indexOf:$*.
        sF1 := sourceUnit copyTo:(i - 1).
        sF2 := sourceUnit copyFrom:(i + 1).

        "/ see what we have ...

        self units do:[:aUnit |
            |pref iUnit factor2 rslt|

            pref := sF1 , '*'.
            (aUnit startsWith:pref) ifTrue:[
                "/ ok; want a/b -> x
                "/ found a/c -> any
                "/ what about c->b ?

                iUnit := aUnit copyFrom:pref size + 1.
                factor2 := self convert:1 from:sF2 to:iUnit.
                factor2 notNil ifTrue:[
                    "/ good ...
                    rslt := self convert:(factor2 * howMany)
                                    from:aUnit to:destUnit.
                    rslt notNil ifTrue:[^ rslt].
                ]
            ]
        ].
    ].

    ^ self noConversionFrom:sourceUnit to:destUnit.

    "direct - how many meters are there in two inches:
     UnitConverter convert:2 from:#inch to:#meter     
     UnitConverter convert:37 from:#degrees to:#fahrenheit     

     reverse - how many inches are there in one meter
     UnitConverter convert:1 from:#meter to:#inch   

     with alias:
     UnitConverter convert:1 from:#inch to:#m    
     UnitConverter convert:1 from:#inch to:#mm          
     UnitConverter convert:1 from:#inch to:#millimeter   
     UnitConverter convert:1 from:#inch to:#nanometer 
     UnitConverter convert:1 from:#mm to:#km  
     UnitConverter convert:1 from:#km to:#foot   

     indirect:
     UnitConverter convert:1 from:#mm   to:#twip  
     UnitConverter convert:1 from:#inch to:#twip  
     UnitConverter convert:1 from:'letterH' to:#point  
     UnitConverter convert:1 from:'letterlH' to:#point  

     UnitConverter convert:5 from:#barrel to:#liter  
     UnitConverter convert:10 from:#kilogram to:#carat  

     UnitConverter convert:1 from:#liter to:#floz  
    "

    "Created: 31.5.1996 / 16:23:38 / cg"
    "Modified: 6.8.1997 / 18:10:22 / cg"
!

fileSizeStringFor:nBytes
    |unitString n|

    nBytes < (500 * 1024 * 1024) ifTrue:[
        nBytes < (500 * 1024) ifTrue:[
            nBytes < 1024 ifTrue:[
                n := nBytes.
                unitString := '   '.
            ] ifFalse:[
                n := (nBytes * 10 // 1024 / 10.0).
                unitString := ' K'
            ]
        ] ifFalse:[
            n := (nBytes * 10 // 1024 // 1024 / 10.0).
            unitString := ' M'
        ].
    ] ifFalse:[
        n := (nBytes * 10 // 1024 // 1024 // 1024 / 10.0).
        unitString := ' G'
    ].

    ^ n printString , unitString.

    "
     self fileSizeStringFor:10          
     self fileSizeStringFor:100            
     self fileSizeStringFor:1000           
     self fileSizeStringFor:10000          
     self fileSizeStringFor:100000      
     self fileSizeStringFor:1000000        
     self fileSizeStringFor:10000000       
     self fileSizeStringFor:100000000      
     self fileSizeStringFor:1000000000      
     self fileSizeStringFor:10000000000      
    "
!

inchToMillimeter:inches
    "convert inches to mm. Made this an extra method, since its so common."

    ^ inches * 25.4

    "Created: 31.5.1996 / 13:37:31 / cg"
    "Modified: 31.5.1996 / 18:08:14 / cg"
!

millimeterToInch:mm
    "convert mm to inches. Made this an extra method, since its so common."

    ^ mm / 25.4

    "Created: 31.5.1996 / 13:37:48 / cg"
    "Modified: 31.5.1996 / 18:08:20 / cg"
! !

!UnitConverter class methodsFor:'missing conversion'!

noConversionFrom:sourceUnit to:destUnit
    Transcript showCR:'no conversion ' , sourceUnit printString , ' -> ' , destUnit printString.
    ^ nil

    "Created: 29.3.1997 / 17:56:03 / cg"
! !

!UnitConverter class methodsFor:'private'!

addConversion:factor from:sourceMetric to:destMetric
    "add a conversion"

    |conversion|

    conversion := Conversions at:sourceMetric ifAbsent:nil.
    conversion isNil ifTrue:[
	conversion := IdentityDictionary new.
	Conversions at:sourceMetric put:conversion
    ].
    conversion at:destMetric put:factor.
    ^ conversion

    "Created: 31.5.1996 / 13:51:25 / cg"
    "Modified: 29.3.1997 / 17:19:31 / cg"
!

convertDirect:howMany from:sourceMetric to:destMetric
    "given a value in sourceMetric (symbolic), try to convert it
     to destMetric (symbolic); 
     Only direct conversions are tried; return nil, if the conversion is unknown."

    |conversion factor|

    Conversions isNil ifTrue:[
	self initializeConversions
    ].

    conversion := Conversions at:sourceMetric ifAbsent:nil.
    conversion isNil ifTrue:[^ nil].

    factor := conversion at:destMetric ifAbsent:nil.
    factor isNil ifTrue:[^ nil].

    factor isNumber ifTrue:[
	^ howMany * factor
    ].
    ^ factor value:howMany

    "
     UnitConverter convertDirect:1 from:#inch to:#meter 
     UnitConverter convertDirect:1 from:#inch to:#millimeter 
     UnitConverter convertDirect:1 from:#degrees to:#fahrenheit 
    "

    "Created: 31.5.1996 / 13:54:33 / cg"
    "Modified: 22.7.1997 / 13:57:52 / cg"
!

unscaled:what
    "given a unit, return the base and a factor as assoc,
     or nil if not found"

    Conversions isNil ifTrue:[
	self initializeConversions
    ].

    Scaling keysAndValuesDo:[:name :factor |
	|rest|

	(what startsWith:name) ifTrue:[
	    rest := what copyFrom:(name size+1).
	    rest := rest asSymbolIfInterned.
	    rest notNil ifTrue:[
		^ rest -> factor.
	    ]        
	].
    ].
    ^ nil

    "
     UnitConverter unscaled:#millimeter
     UnitConverter unscaled:#nanometer 
     UnitConverter unscaled:#kilometer   
     UnitConverter unscaled:#fuzzymeter   
    "

    "Modified: 22.7.1997 / 13:57:46 / cg"
! !

!UnitConverter class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/UnitConverter.st,v 1.23 2003-01-09 17:16:59 cg Exp $'
! !