[Haskell-cafe] Inheritance without OOHaskell

Bulat Ziganshin bulatz at HotPOP.com
Sat Jan 14 05:02:45 EST 2006


Hello Cale,

Saturday, January 14, 2006, 12:22:08 AM, you wrote:

CG> On 13/01/06, John Goerzen <jgoerzen at complete.org> wrote:

i want to answer, but Gale covered all that i have to say :)  the only
additions is that i use more old-fashioned Hugs-compatible declarations
instead of GADT-style

CG> data Connection where
CG>     Conn :: (IsConnection c) => c -> Connection

data Connection = forall c . (IsConnection c) => Conn c


and that i use the "delegation" pattern:

class (Show h) => Stream h where
    vClose :: h -> IO ()
    ......
    vSetEncoding :: h -> Encoding -> IO ()
    vGetEncoding :: h -> IO Encoding
    

data WithEncoding h = WithEncoding h (IORef Encoding)

openWithEncoding encoding h = do
    e <- newIORef encoding
    return (WithEncoding h e)

instance (Stream h) => Stream (WithEncoding h) where
    vClose        (WithEncoding h _) = vClose     h
    vIsEOF        (WithEncoding h _) = vIsEOF     h
    vMkIOError    (WithEncoding h _) = vMkIOError h
    vReady        (WithEncoding h _) = vReady     h
    ......
    vSetEncoding  (WithEncoding h e) = writeIORef e
    vGetEncoding  (WithEncoding h e) = readIORef  e
    
you can see WithEncoding type as a one adding server-specific features
to general driver implementation. of course, this idea of "stream
transformers" is more general that you really requested, but the
"delegation" pattern will remain the same


-- 
Best regards,
 Bulat                            mailto:bulatz at HotPOP.com





More information about the Haskell-Cafe mailing list