[Haskell-cafe] Fwd: Object Oriented programming for Functional Programmers

2012-12-30 Thread Eli Frey
sorry, forgot to reply-all

-- Forwarded message --
From: Eli Frey eli.lee.f...@gmail.com
Date: Sun, Dec 30, 2012 at 1:56 PM
Subject: Re: [Haskell-cafe] Object Oriented programming for Functional
Programmers
To: Brandon Allbery allber...@gmail.com


 Except not quite... [...] It's not a built in table, it's a hidden
parameter.

I'll admit this doesn't HAVE to be the implementation.  Often time the
compiler can monomorphise the types and perform the lookup at compile
time.

But what's going on here tho.

 {-# LANGUAGE ExistentialQuantification #-}
  data Showable = forall a. Show a = Showable a

 printShowable :: Showable - IO ()
 printShowable (Showable x) = print x

  main = mapM printShowable [ Showable bob, Showable 3, Showable Nothing
]

If we take `mapM printShowable` and just give it an arbitrary list, it has
to lookup the correct implementations of `print` as it walks down that list
at run-time.  I believe similar things motivate vtables in c++/java.  I
don't have a strong intuition about how dynamically typed OO langs deal
with this, but I'm sure structural typing has similar issues.


On Sun, Dec 30, 2012 at 1:27 PM, Brandon Allbery allber...@gmail.comwrote:

 On Sun, Dec 30, 2012 at 3:45 PM, Eli Frey eli.lee.f...@gmail.com wrote:

  mconcat :: Monad m = [m] - m
  mconcat = foldl mappend []

 We can think of `mconcat` having a little lookup table inside of itself,
 and whenever we pass it a concrete `[m]`, `mappend` gets looked up and we
 get the implementation for `m`.  Typeclasses are just mappings from types
 to functions


 Except not quite... the Monad m = in the signature really means hey,
 compiler, pass me the appropriate implementation of Monad so I can figure
 out what I'm doing with this type m.  It's not a built in table, it's a
 hidden parameter.

 Aside from Object Orientation, it is probably a good idea to learn some C
 for a bit too.  C is a good language to play in and try and implement more
 advanced language features.  Once you reallize that objects are just lookup
 tables of functions bound with a data-structure, you can implement your own
 in C, or you can make closures as functions bundled with (some) of their
 arguments, or you can implement interesting datastructures, or so many
 other fun things.  A good understanding of tagged unions has helped me in
 many a convo with an OO head.


 A perhaps strange suggestion in this vein:  dig up the source code for Xt,
 the old X11 Toolkit, and the Xaw widget library that is built atop it.
  (It's part of the X11 source tree, since most of the basic X11 utilities
 and xterm are based on it.)  It implements a primitive object system in C.
  Gtk+ does the same, but hides much of the implementation behind macros and
 relies on tricky casting etc. behind the scenes for performance; in Xt, the
 basic machinery is more easily visible for inspection and much easier to
 understand even if you're not all that familiar with C.  If you go this
 way, once you've figured out what Xt is doing you might go on to see the
 more advanced concepts in how Gtk+ does it.

 And once you've done this, you'll have a good idea of what Objective-C and
 C++ (minus templates) are doing under the covers.  (Mostly C++, since ObjC
 is more or less Smalltalk's OO on top of X, whereas the core concepts of
 C++ are not so very different from what Xt does.)  If you really want to
 dig in further, you might want to try to find the source to cfront, the
 original C++ implementation which was a preprocessor for the C compiler.
  It'll be missing a lot of modern C++ features, but the core is there.

 --
 brandon s allbery kf8nh   sine nomine
 associates
 allber...@gmail.com
 ballb...@sinenomine.net
 unix, openafs, kerberos, infrastructure, xmonad
 http://sinenomine.net

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fwd: Object Oriented programming for Functional Programmers

2012-12-30 Thread Timon Gehr

On 12/30/2012 10:57 PM, Eli Frey wrote:

sorry, forgot to reply-all

-- Forwarded message --
From: *Eli Frey* eli.lee.f...@gmail.com mailto:eli.lee.f...@gmail.com
Date: Sun, Dec 30, 2012 at 1:56 PM
Subject: Re: [Haskell-cafe] Object Oriented programming for Functional
Programmers
To: Brandon Allbery allber...@gmail.com mailto:allber...@gmail.com


  Except not quite... [...] It's not a built in table, it's a hidden
parameter.

I'll admit this doesn't HAVE to be the implementation.  Often time the
compiler can monomorphise the types and perform the lookup at compile
time.

But what's going on here tho.

  {-# LANGUAGE ExistentialQuantification #-}
   data Showable = forall a. Show a = Showable a
 
  printShowable :: Showable - IO ()
  printShowable (Showable x) = print x
 
   main = mapM printShowable [ Showable bob, Showable 3, Showable
Nothing ]

If we take `mapM printShowable` and just give it an arbitrary list, it
has to lookup the correct implementations of `print` as it walks down
that list at run-time.  I believe similar things motivate vtables in
c++/java.  I don't have a strong intuition about how dynamically typed
OO langs deal with this, but I'm sure structural typing has similar issues.

...


The Showable constructor has two parameters. The 'Show' instance for 'a' 
(passed implicitly) and an 'a' (passed explicitly). When pattern 
matching, that instance gets unwrapped together with the payload. It is 
then implicitly passed to 'print', which finally uses it to look up the 
correct implementation of 'show'.




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe