On 27/02/2004, at 1:13 PM, [EMAIL PROTECTED] wrote:

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)

Very, very nice Oleg :). I'm glad to know that we can achieve such things using the existing type class mechanisms already. However, this still doesn't solve the problem, because:


1) now I have to manually declare a class definition for every single function, and I have to declare it in advance before any module defines that function (most serious problem; see below),

2) I then have to declare instances of that type class for every function I define,

3) the type signature for phase reveals no clues about how to use that function.

So unfortunately, this is hardly a scalable solution. The entire reason I came up with the idea is because if we use type classes to implement this sort of overloading, we have to know every single possible function that any module author will ever create, and declare classes for those functions in advance. This is fine if you're declaring truly polymorphic functions which are designed from the start to be totally general, but it is not designed for functions which may do vastly different things and may contain totally different type signatures, but share the same name because that would be a sensible thing to do. (e.g. the phase function mentioned above.)

With the per-type namespace separation I'm advocating, you do not need to know and declare in advance that each function "will be" overloaded, you simply write a FiniteMap.add function and a Set.add function, and you get a simpler form of namespace separation (or overloading) based on the first parameter that's passed to it. It is a solution which is more _flexible_ than requiring type class definitions, and it is better than having hungarian notation for functions. In fact, I think that, right now, if we replaced the current namespace separation offered by the hierarchical module system, and instead only had this sort of per-type namespace separation, things would still be better!

I realise my idea isn't very general in that it only allows this namespace lookup/overloading based on the type of a single argument parameter, and I think it would be possible with a bit more thinking to generalise it to work based on multiple arguments (e.g. via argument-dependent lookup, or whatnot). But even in its current form, I honestly think it offers far more flexibility and would lead to cleaner APIs than is currently possible.


-- % Andre Pang : trust.in.love.to.save _______________________________________________ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Reply via email to