The recent suggestion that OO and FP are somewhat out of phase reminds
me of a pet topic: overlapping types.  This is (IMHO) the only feature
of OO for which there is (AFAICS) no FP equivalent.

Here's a more concrete proposal than my previous vague rants on the
subject.

    module Treat where

    class Subtype sub super where
        up   :: sub   -> super
        down :: super -> Maybe sub

    --Should Subtype be reflexive?
    instance Subtype a a where
        up   x = x
        down x = Just x

    --Subtype should be transitive; I may have done something evil
    --here, because Classic Hugs (November 1999) with the `-98' flag
    --rejects this decl with the message `Undefined type variable "b"'
    instance (Subtype a b, Subtype b c) => Subtype a c where
        up   x = up (up x)
        down z = down z >>= down

    --Law: down (up x) === Just x
    --     (not enforced by the compiler, cf. unit laws for monads)

    --Law: if two types have any common supertypes, they have exactly
    --     one most specific common supertype, which is a subtype of
    --     all their other common supertypes
    --     (enforced by the compiler)

The Subtype class would have this special meaning in the language:

    When unifying two types, the compiler must explore the possibility
    of treating them up to their most specific common supertype.

A notable place where Haskell could benefit from overlapping types is
the treatment of numeric types, with its many special cases.  We could
express our knowledge that every Integer is a Rational thus:

    instance Integral a => Subtype a (Ratio a) where
        up   i                      = i % 1
        down r | denominator r == 1 = Just (numerator r)
               | otherwise          = Nothing

...and use it thus:

    Treat> up (3 :: Integer) :: Rational
    3 % 1
    Treat> down (4 % 2 :: Rational) :: Maybe Integer
    Just 2
    Treat> down (5 % 2 :: Rational) :: Maybe Integer
    Nothing

The programmer would use the Treat.down function but generally ignore
the Treat.up function.  After all, the untreated 0::Int would be
acceptable in all the same places as the treated 0::Integer and some
more besides.

I've had a look at subtyping in O'Haskell:

    http://www.cs.chalmers.se/~nordland/ohaskell/survey.html#sect4

which differs in that it has a very nice succinct syntax, but AFAICS
won't handle abstract data types, and only supports subtyping by
extending products and reducing sums.

This proposal also resembles a part of Sergey's basAlgPropos.  It's a
part which I think should be considered in isolation from the rest.

So... comments please!  I'm happy to formulate the typechecking aspect
of the proposal in terms of THIH (http://www.cse.ogi.edu/~mpj/thih/),
if it'll help anyone.

Regards,
Tom

Reply via email to