[Haskell] What is the best way to write adapters?

oleg at pobox.com oleg at pobox.com
Thu Mar 11 11:36:30 EST 2004


> The code is currently like this:

> instance Sig Def where
>   getName (DefClass c) = getName c
>   getName(DefProtocol p) getName p
>   getName(DefSignature s) = getName s
>   getParents(DefClass c) = getParents c
>   getParents(DefProtocol p) = getParents p
> blah blah blah...
>
> But this seems very annoying.
>
> If I have 4 different constructors in Def, and 5 methods of class Sig,
> (Please bear with me if I'm using some OO terminology because I'm still a
> new FP programmer), I'll have to write 4*5=20 forwarding functions.

Adapters seem by necessity higher-ranked functions. The following is
a stubefied code that uses generic adaptors (the function fwd).

> {-# OPTIONS -fglasgow-exts #-}
> module Foo where
>
> class Sig a where
>   getName :: a -> Int
>   getParents :: a -> String
>   getMethods :: a -> String
>
> data ClassDef = ClassDef
> data ProtocolDef = ProtocolDef
>
> instance Sig ClassDef where
>     getName _ = 0
>     getParents _ = "ClassDef Parents"
>     getMethods _ = "ClassDef Methods"
>
> instance Sig ProtocolDef where
>     getName _ = 1
>     getParents _ = "ProtocolDef Parents"
>     getMethods _ = "ProtocolDef Methods"
>    
> data Def = DefClass ClassDef | DefProtocol ProtocolDef
>
> fwd::(forall a. Sig a => a -> w) -> Def -> w
> fwd f (DefClass c) = f c
> fwd f (DefProtocol p) = f p
>
> instance Sig Def where
>     getName = fwd getName
>     getParents = fwd getParents
>     getMethods = fwd getMethods

Tests:

*Foo> getParents ClassDef
"ClassDef Parents"
*Foo> getParents ProtocolDef
"ProtocolDef Parents"
*Foo> getParents (DefClass ClassDef)
"ClassDef Parents"
*Foo> getParents (DefProtocol ProtocolDef)
"ProtocolDef Parents"


More information about the Haskell mailing list