Tom Pledger wrote:
> 
> Where do units of measure fit into a type system?

In Haskell this should be quite easy. Off my head I would suggest
something like

        class Unit a where
                unit  :: Float -> a
                value :: a -> Float

        newtype Metres  = Metres Float
        newtype Seconds = Seconds Float

        instance Unit Metres where
                unit = Metres
                value(Metres x) = x
        instance Unit Seconds where
                unit = Seconds
                value(Seconds x) = x

        newtype Prod a b = Prod Float
        newtype Quot a b = Quot Float

        instance (Unit a, Unit b) => Unit(Prod a b) where
                unit = Prod
                value(Prod x) = x
        instance (Unit a, Unit b) => Unit(Quot a b) where
                unit = Quot
                value(Quot x) = x

        infix 7 *$, /$
        infix 6 +$, -$

        (+$) :: (Unit a) => a -> a -> a
        (-$) :: (Unit a) => a -> a -> a
        (*$) :: (Unit a, Unit b) => a -> b -> Prod a b
        (/$) :: (Unit a, Unit b) => a -> b -> Quot a b
        x +$ y = unit(value x + value y)
        x -$ y = unit(value x - value y)
        x *$ y = Prod(value x * value y)
        x /$ y = Quot(value x / value y)

        m  = Metres 5
        s  = Seconds 2
        m' = m +$ m             -- OK: Metres
        m2 = m *$ m             -- OK: Prod Metres Metres
        v  = m /$ s             -- OK: Quot Metres Seconds
        a  = m /$ (s *$ s)      -- OK: Quot Metres (Prod Seconds Seconds)
        x  = m -$ s             -- error

It would be nicer if Haskell had infix type constructors:

       newtype a :* b = Prod Float
        newtype a :/ b = Quot Float

Cheers,

        - Andreas

-- 
Andreas Rossberg, [EMAIL PROTECTED]

:: be declarative. be functional. just be. ::


Reply via email to