Interesting Thread on OO Usefulness (scala mailing list)

Hi all, I'm following an interesting thread on the scala mailing list: http://www.nabble.com/-scala--usefulness-of-OOP-td23268250.html Martin Odersky advocates the OO features of the scala language proposing an interesting problem where the OO approach seams valuable. I would be very much interested in seeing an Haskell solution to that problem. Any haskell guru want to take a stub at it or give an opinion from a pure FP point of view? Thanks Paolo

Hello Paolo, Monday, May 4, 2009, 2:05:44 PM, you wrote:
Martin Odersky advocates the OO features of the scala language proposing an interesting problem where the OO approach seams valuable.
i know two problems in Haskell/GHC that require OO-loke features - extensible exceptions and GUI widget types hierarchy -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Bulat Ziganshin wrote:
Hello Paolo,
Monday, May 4, 2009, 2:05:44 PM, you wrote:
Martin Odersky advocates the OO features of the scala language proposing an interesting problem where the OO approach seams valuable.
i know two problems in Haskell/GHC that require OO-loke features - extensible exceptions and GUI widget types hierarchy
Yes, type hierarchies require OO. But, do we really need to represent different widget-types in a hierarchy? An alternative to a big hierarchy would be to let different widget-types implement different type classes. We could have type classes like MouseEvents, KeyboardEvents, Activated, ... /Mads Lindstrøm

Hello Mads, Monday, May 4, 2009, 7:01:16 PM, you wrote:
i know two problems in Haskell/GHC that require OO-loke features - extensible exceptions and GUI widget types hierarchy
Yes, type hierarchies require OO.
But, do we really need to represent different widget-types in a hierarchy?
An alternative to a big hierarchy would be to let different widget-types implement different type classes. We could have type classes like MouseEvents, KeyboardEvents, Activated, ...
there is obvious difference between OOP and type class hierarchies - OOP ones includes data fields. (somewhat close functionality provided by extensible records, but they are not in GHC nor provide strong type-checking) this means a lot of boilerplate code written, i.e. we lose compared to OOP -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Am Montag, 4. Mai 2009 13:35 schrieb Bulat Ziganshin:
Hello Paolo,
Monday, May 4, 2009, 2:05:44 PM, you wrote:
Martin Odersky advocates the OO features of the scala language proposing an interesting problem where the OO approach seams valuable.
i know two problems in Haskell/GHC that require OO-loke features - extensible exceptions and GUI widget types hierarchy
Note that you don’t need different types for different kinds of GUI widgets if you use Functional Reactive Programming (FRP). You need different types if you use OO because you have to explicitely modify widgets after you have created them, and what modifications you are allowed to do, depends on the kind of widget. With FRP, you specify the behavior over all time when you create the widget, so no need for later method calls. Best wishes, Wolfgang

Hello Wolfgang, Tuesday, May 5, 2009, 8:27:17 PM, you wrote:
i know two problems in Haskell/GHC that require OO-loke features - extensible exceptions and GUI widget types hierarchy
Note that you don’t need different types for different kinds of GUI widgets if you use Functional Reactive Programming (FRP). You need different types if you use OO because you have to explicitely modify widgets after you have created them, and what modifications you are allowed to do, depends on the kind of widget. With FRP, you specify the behavior over all time when you create the widget, so no need for later method calls.
(i don't know anything about FRP) i think it doesn't change anything. the main reason why i need common operations is because i write generic procedures. another erason os what i can't remember 100 individual 'setSize' operations for 100 types of widgets. so we need to have some generic names, short of they are used due initialization or later -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Am Dienstag, 5. Mai 2009 18:39 schrieb Bulat Ziganshin:
Hello Wolfgang,
Tuesday, May 5, 2009, 8:27:17 PM, you wrote:
i know two problems in Haskell/GHC that require OO-loke features - extensible exceptions and GUI widget types hierarchy
Note that you don’t need different types for different kinds of GUI widgets if you use Functional Reactive Programming (FRP). You need different types if you use OO because you have to explicitely modify widgets after you have created them, and what modifications you are allowed to do, depends on the kind of widget. With FRP, you specify the behavior over all time when you create the widget, so no need for later method calls.
(i don't know anything about FRP)
i think it doesn't change anything. the main reason why i need common operations is because i write generic procedures. another erason os what i can't remember 100 individual 'setSize' operations for 100 types of widgets. so we need to have some generic names, short of they are used due initialization or later
Yes, you need generic names also with FRP. The difference is that with OO, every property (e.g., size) corresponds to a pair of methods (setSize, getSize) while in FRP every property correspond to an input (or a parameter of the constructor if you think in OO terms). So with FRP, you need some kind of record system, preferably with the possibility to extend records. At least, this is the solution I use in Grapefruit. Best wishes, Wolfgang

This sounds like a really interesting question. To save some people weeding
through the thread and Jon Harrop's usual trolling garbage, here's a
description of the problem:
[quote]
Here's [a]language to to interpret (where postfix * means tupling):
Variables: x
Integer literals: i
Terms:
t = Lambda x*. t
| Apply t t*
| Var(x)
| Num(i)
We assume usual operational semantics of lambda calculus (i.e. static
scoping).
The task is to write two interpreters, one with variables x being
DeBruijn indices and one with them being names.
You should go for maximal sharing, i.e. factor out commonalities into
a common class/typeclass/functor/whatever, so that there remains no
duplication of code in the two solutions.
[/quote]
On Mon, May 4, 2009 at 6:05 AM, Paolo Losi
Hi all,
I'm following an interesting thread on the scala mailing list:
http://www.nabble.com/-scala--usefulness-of-OOP-td23268250.html
Martin Odersky advocates the OO features of the scala language proposing an interesting problem where the OO approach seams valuable.
I would be very much interested in seeing an Haskell solution to that problem. Any haskell guru want to take a stub at it or give an opinion from a pure FP point of view?
Thanks Paolo
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Andrew Wagner wrote:
[quote] Here's [a]language to to interpret (where postfix * means tupling):
Variables: x Integer literals: i Terms:
t = Lambda x*. t | Apply t t* | Var(x) | Num(i)
Can someone explain to me how I should read this? It supposedly explains what the postfix * means ("tupling") but I still can only guess how it translates to a Haskell datatype. Thanks, Martijn.

On Mon, May 04, 2009 at 03:08:25PM +0200, Martijn van Steenbergen wrote:
Andrew Wagner wrote:
[quote] Here's [a]language to to interpret (where postfix * means tupling): Variables: x Integer literals: i Terms: t = Lambda x*. t | Apply t t* | Var(x) | Num(i)
Can someone explain to me how I should read this? It supposedly explains what the postfix * means ("tupling") but I still can only guess how it translates to a Haskell datatype.
I think t* is supposed to represent an arbitrary number (a tuple) of t's. So in Haskell syntax, you can read t* as [t]. Hence, the language described above is not curried: lambda expressions can have any finite number of arguments, and applications are correspondingly some term applied to a tuple of arguments. -Brent

ML functors seem the ideal tool for this task. People have shown how you
can emulate them with typeclasses, but it won't necessarily be pretty...
On Mon, May 4, 2009 at 4:05 AM, Paolo Losi
Hi all,
I'm following an interesting thread on the scala mailing list:
http://www.nabble.com/-scala--usefulness-of-OOP-td23268250.html
Martin Odersky advocates the OO features of the scala language proposing an interesting problem where the OO approach seams valuable.
I would be very much interested in seeing an Haskell solution to that problem. Any haskell guru want to take a stub at it or give an opinion from a pure FP point of view?
Thanks Paolo
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi, Paolo Losi wrote:
I'm following an interesting thread on the scala mailing list:
http://www.nabble.com/-scala--usefulness-of-OOP-td23268250.html
Martin Odersky advocates the OO features of the scala language proposing an interesting problem where the OO approach seams valuable.
I would be very much interested in seeing an Haskell solution to that problem.
Here is my take on it, using type families. Tillmann {-# LANGUAGE TypeFamilies #-} import Data.List (elemIndex) -- COMMON INTERFACE -- -- environments and variables class Env env where data V env empty :: env a bind :: (String, a) -> env a -> env a find :: env a -> V env -> a -- too bad we have to include these here :( showVar :: Int -> V env -> ShowS showEnv :: Show a => Int -> env a -> ShowS -- GENERIC INTERPRETER -- -- terms (for some type of variables v) data T env = Lam [String] (T env) | App (T env) [T env] | Var (V env) | Lit Integer instance Env env => Show (T env) where showsPrec p t = showParen (p > 10) $ case t of Lam vs t -> ("Lam " ++) . showsPrec 11 vs . (' ' :) . showsPrec 11 t App f xs -> ("App " ++) . showsPrec 11 f . (' ' :) . showsPrec 11 xs Var v -> ("Var " ++) . showVar 11 v Lit n -> ("Lit " ++) . showsPrec 11 n -- domain of values data D env = Fun [String] (T env) (env (D env)) | Num Integer instance Env env => Show (D env) where showsPrec p t = showParen (p > 10) $ case t of Fun vs t env -> ("Fun " ++) . showsPrec 11 vs . (' ' :) . showsPrec 11 t . (' ' :) . showEnv 11 env Num n -> ("Num " ++) . showsPrec 11 n -- interpreter eval :: Env env => env (D env) -> T env -> D env eval env (Lam vs t) = Fun vs t env eval env (App f xs) = apply (eval env f) (map (eval env) xs) eval env (Var v ) = find env v eval env (Lit n ) = Num n apply :: Env env => D env -> [D env] -> D env apply (Fun vs t env) xs | length vs == length xs = eval env' t | otherwise = error ("arity mismatch: " ++ show vs ++ ", " ++ show xs) where env' = foldr bind env (zip vs xs) apply (Num n) xs = error "not a function" -- VARIABLES AS STRINGS -- data AssocList a = AssocList [(String, a)] deriving Show instance Env AssocList where data V AssocList = Name String deriving Show empty = AssocList [] bind (v, x) (AssocList env) = AssocList ((v, x) : env) find (AssocList env) (Name v) = case lookup v env of Just x -> x Nothing -> error "free variable" showVar = showsPrec showEnv = showsPrec -- VARIABLES AS De-BRUIJN INDICES -- data Stack a = Stack [a] deriving Show instance Env Stack where data V Stack = Index Int deriving Show empty = Stack [] bind (v, x) (Stack env) = Stack (x : env) find (Stack env) (Index v) = if v < length env then env !! v else error "free variable" showVar = showsPrec showEnv = showsPrec -- CONVERT NAMES TO DE-BRUIJN INDICES -- index :: [String] -> T AssocList -> T Stack index vs (Lam ws t ) = Lam ws (index (ws ++ vs) t) index vs (App f xs ) = App (index vs f) (map (index vs) xs) index vs (Var (Name v)) = case elemIndex v vs of Just n -> Var (Index n) Nothing -> error "free variable" index vs (Lit n ) = Lit n -- TEST -- identity = Lam ["x"] (Var (Name "x")) two = Lam ["f", "x"] (App (Var (Name "f")) [(App (Var (Name "f")) [(Var (Name "x"))])]) five = App two [identity, Lit 5] test = case (eval empty five, eval empty (index [] five)) of (Num 5, Num 5) -> True _ -> False
participants (9)
-
Andrew Wagner
-
Brent Yorgey
-
Bulat Ziganshin
-
Luke Palmer
-
Mads Lindstrøm
-
Martijn van Steenbergen
-
Paolo Losi
-
Tillmann Rendel
-
Wolfgang Jeltsch