Hello!

> So, how can you come up with a type class which provides a polymorphic
> 'add' function, considering you don't even know how many parameters
> each data type's individual add function uses?

Very easily: every Haskell function takes only one
argument. Always. Ever.

> For example, say I'm writing the Data.Complex module; there's a
> function in that module "phase :: RealFloat a => Complex a -> a".  So,
> how do you put this phase function into a type class?  Perhaps you
> could abstract away from the RealFloat and Complex bits, so you have a
> phase function which is generalised to work over a Num and an
> arbitrary data type instead; e.g. "class Phase c where phase :: Num a
> => c a -> a".  But what happens if, say, somebody adds a Moon data
> type, and they want to write a phase function which returns the phase
> of such a moon?  Phases of the moon certainly aren't Nums, nevermind
> the fact that you probably want to supply your moon phase's function
> with some sort of date as an extra parameter, which means the Phase
> type class isn't flexible enough.

Here's the code that does exactly as you wish:

> {-# OPTIONS -fglasgow-exts #-}
>
> import qualified Complex 
>
> class Phase a b | a -> b where
>   phase:: a -> b
> 
>
> instance (RealFloat a) => Phase (Complex.Complex a) a where
>     phase = Complex.phase
>   
> data MoonPhase = P1 | P2 | P3 | P4 deriving Show
>
> instance Phase Int MoonPhase where
>     phase x = if x `mod` 4 == 0 then P1 else P4
>   
> instance Phase MoonPhase (Int->Int) where
>     phase P1 x = x
>     phase P2 x = x+1
>
> main = do
>         putStrLn $ show $ phase ( (1.0::Float) Complex.:+ (1.0::Float))
>         putStrLn $ show $ phase (0::Int)
>         putStrLn $ show $ phase P1 (2::Int)

You can evaluate a phase of a complex number, get a phase of the moon
corresponding to some integer, and even convert a phase of the moon to
a time (given another integer as a reference time). Whereas the first
two functions take one argument, the latter phase takes "two
arguments". The class Phase takes the classical first-argument
overloading. Other overloading schemes are possible (e.g., the ones
that overload based on the result -- something that C++ just can't do:
e.g., Read). If we need to evaluate phases of Saturn moons (and we
overload on the first argument), we can resolve the overloading using
newtype:

> newtype SaturnTime a = ST a
> instance Phase (SaturnTime Int) (Int -> MoonPhase) where
>    phase x moon_index = P1

newtypes add no run-time overhead, and actually help in making the
code more explicit.

Regarding Koening lookup: as I read in DDJ, it's just a hack! First
the committee added the namespaces, and then realized that using
operators like << became hugely inconvenient. So Koening came up with
a hack. Shouldn't a language be designed in a more systematic way?

Speaking of the language design, November 2003 issue of Dr.Dobbs
J. has an interesting article: "C++ Compilers and ISO Conformance" [by
Brian A. Malloy, James F. Power and Tanton H. Gibbs, pp. 54-60].

Here's a summary. C++ standard has been ratified by the ISO Committee
in September 1998. There is no conformance suite however. So, we
cannot tell how well a particular compiler complies with a
standard. The authors of an article decided to create an approximate
conformance suite -- from the examples given in the standard
itself. It's a hard job -- the examples aren't meant to be a compiled
code, so some declarations and other pieces have to be filled in. The
result cannot be considered a truly compliance suite because not all
features of the language are illustrated in examples, and the
distribution of the examples is uneven. Nevertheless, it's a start.

The authors of the article have tested several compilers. The bottom
line -- after five years, no single compiler fully complies with the
standard. The best compiler, from the Edison Group (a three-person
company) fails only 2 tests. Intel's compiler fails three. Visual C++
7.1 from Microsoft fails 12. Gcc 3.3 fails 26. The latter number shows
that a wide community participation and OpenSource do not necessarily
lead to a better product. Gcc 3.3 is also one of the slowest
compilers.

But there is worse news for C++. C++ Language Standard consists of 776
pages, describing C++ language and the C++ core library. At present,
411 points in the C++ language part and 402 points in the library
part have been identified as questionable or outright erroneous. 93
language issues have been already acknowledged as errors. That is,
EVERY page of the standard, on average, contains some issue! The
committee obviously didn't bother to check their examples. Well, even
now there isn't a compiler that complies with the standard -- whatever
the compliance may mean.

Not only programmers don't know what some C++
rules mean. Not only compiler writers are puzzled. Even the committee
itself obviously doesn't know how _many_ features are supposed to
work. Can you imagine more shoddy work? 

Incidentally, here's one questionable example from the standard (which
has been acknowledged as an error in the Technical Corrigendum 1). 

typedef int f;
struct A {
   friend void f(A &);
   operator int ();
   void g(A a) { f(a); } 
};

f(a) is ambiguous: it could mean an invocation of method A.f. OTH, it
may mean casting 'a' to an integer: f(a) may read int(a) (if typedef
takes effect), which is a cast. Both interpretations are valid. The
authors of the standard assumed that a compiler could
disambiguate. After the compiler writers tried and failed, the
committee admitted that perhaps the example shouldn't compile after
all.
_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to