UnitConverter.st
author Claus Gittinger <cg@exept.de>
Tue, 15 Oct 1996 22:35:55 +0200
changeset 450 efbbe6d6c6f5
parent 385 67ac6014097c
child 453 0a340127d3af
permissions -rw-r--r--
removed unused vars

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

!UnitConverter class methodsFor:'documentation'!

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 have 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 units supported 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
    and many others.

    [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]
    or, how many square-meters an acre is:
                                                                [exBegin]
        Transcript showCR:
            (UnitConverter convert:1 from:#acre to:#meter2)
                                                                [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:#meter2 to:#foot2)   
                                                                [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]
"
!

history

    "Created: 31.5.1996 / 13:34:29 / cg"
    "Modified: 31.5.1996 / 14:54:34 / cg"
! !

!UnitConverter class methodsFor:'initialization'!

initialize
    "initialize common conversions"

    Scaling := IdentityDictionary new.
    Conversions := IdentityDictionary new.
    Aliases := IdentityDictionary new.

    Scaling at:#tera  put:1000000000000.
    Scaling at:#giga  put:1000000000.
    Scaling at:#mega  put:1000000.
    Scaling at:#kilo  put:1000.
    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).

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

    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.


    "/ ---------- printing -------------

    "/ 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'.

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

    "/ US
    self addConversion:4840        from:#acre  to:#yard2.

    self addConversion:100         from:#are      to:#meter2.
    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:#inch3.
    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.

    Aliases at:#cc    put:#cm3.
    Aliases at:#liter put:#kilocc.
    Aliases at:#ml    put:#milliliter.
    Aliases at:#gal   put:#gallon.
    Aliases at:#qt    put:#quart.

    "/ ---------------- mass ---------------- 
    self addConversion:453.59237 from:#lb to:#gram.
    self addConversion:205       from:#carat to:#milligram.

    Aliases at:#oz put:#ounce.

    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:#in3.
    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:#newtom.

    self addConversion:(1 / 4.1868) from:#calorie  to:#joule.

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

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

    "
     UnitConverter initialize
    "

    "Modified: 4.6.1996 / 17:14:46 / 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|

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

    sourceUnit isSymbol ifFalse:[
        sU := sourceUnit asSymbolIfInterned.
        sU isNil ifTrue:[^ nil].
        ^ self convert:howMany from:sU to:destUnit
    ].
    destUnit isSymbol ifFalse:[
        dU := destUnit asSymbolIfInterned.
        dU isNil ifTrue:[^ nil].
        ^ self convert:howMany from:sourceUnit to:dU
    ].

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

    "/ working with squares or cubics ?

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

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

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

    ^ nil

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

     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: 31.5.1996 / 23:11:50 / cg"
!

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

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|

    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 
    "

    "Created: 31.5.1996 / 13:54:33 / cg"
    "Modified: 31.5.1996 / 18:05:39 / cg"
!

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

    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: 31.5.1996 / 14:57:25 / cg"
! !

!UnitConverter class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/UnitConverter.st,v 1.6 1996-10-15 20:35:55 cg Exp $'
! !
UnitConverter initialize!