[Haskell-beginners] Cure me of my OOP ways

Stephen Blackheath [to Haskell-Beginners] mutilating.cauliflowers.stephen at blacksapphire.com
Wed Feb 3 01:19:14 EST 2010


David,

Here's the same code in more idiomatic Haskell:

type API = Int -> Int -> Int
test = 1 + 2
result = test

I am being a smartypants, but only partly - I'm trying to make the point
that partial application essentially replaces the factory pattern from
OO.  If you want to make another subclass, that has some extra internal
data, e.g. 'add then scale by some value'...

addAndScale :: Int -> API
addAndScale f a b = (a + b) * f

as10 = addAndScale 10

result = as10 3 5

These functions can't modify their internal state.  If you want to add
that capability, there are several ways.  Here is one:

newtype API = API {unAPI :: Int -> Int -> (Int, API) }

sumTwo :: Int -> API
sumTwo total = API $ \a b ->
    let total' = total + a + b
    in  (total', sumTwo total')

result =
    let s1 = sumTwo 0
        (_, s2) = unAPI s1 2 2
        (total, s3) = unAPI s2 3 7
    in  total

This returns a new API, which the caller should now use instead of the
old one, and this allows it to maintain state.  The reason for the
newtype is that things defined with 'type' can't be recursive.


Steve

David Gordon wrote:
> Hi Folks,
> 
> I am redesigning a system previously implemented in C++ using Haskell. I
> am keen to adopt a native programming style, but certain things about
> the original implementation still make perfect sense to me, including
> the C++-style subtype polymorphism. I'd be grateful if someone could
> take a look at the following sample and tell me if I'm missing some
> neater possible implementation in Haskell.
> 
> {-# OPTIONS -fglasgow-exts #-}
> -- for existential types
> 
> -- all subclasses take the same input format and can be created
> factory-pattern style
> data Input = Input Int Int
> 
> -- this is the class we have to implement when creating a 'subtype'
> class InternalAPI i where
>     doitImpl :: i -> Input -> Int
> 
>     -- factory function, everything is initialised by giving an "i" and
> the Input
>     create :: i -> Input -> PublicAPI
>     create a b = PublicAPI a b
> 
> -- this is the object clients see, regardless of the underlying
> implementation
> data PublicAPI = forall p. InternalAPI p => PublicAPI p Input
> doit (PublicAPI p i) = doitImpl p i
> 
> -- Here's an example implementation of something trivial
> data Adder = Adder
> instance InternalAPI Adder where
>     doitImpl _ (Input a b) = a + b  -- first argument is superfluous
> 
> -- There's the factory function in use:
> test = create Adder (Input 1 2)
> result = doit test
> 
> I'm actually pretty happy with this. I'm not trying for a complete OOP
> implementation but it lets me:
> - have the 'base class' (InternalAPI) implement default versions of
> methods with full access to the 'Input' structure containing the member data
> - do further inheritance, since I can select the implementation of a
> method using that first argument (e.g. on doitImpl)
> - base and derived classes see the same member data
> - Implementations of 'InternalAPI' can reference each other through the
> PublicAPI interface.
> 
> Admittedly it's a rather vague question. I wonder if there are any
> articles out there showing how to reformulate problems solved using
> C++-style object models into Haskell programs? After all, it's hardly as
> if the C++ model is particularly elegant...
> 
> thanks,
> 
> David
> 
> 
> ------------------------------------------------------------------------
> 
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners


More information about the Beginners mailing list