Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Donald Bruce Stewart
Phlex:
 Hello all,
 
 I'm coming from the OO world, and there's something i don't quite 
 understand in the way haskellers manipulate data (as all functional 
 programmers i guess).
 
 Let's say i have a deep nested data structure.
 Universe containing galaxies, containing solar systems, containing 
 planets, containing countries, containing inhabitants, containing 
 ...whatever.
 
 Using the OO paradigm, once i get a reference to an inhabitant, i can 
 update it quite easily (say by changing it's age), and that's the end of it.
 
 On the other side, using the functional paradigm, it seems to me that 
 the function i use in order to create a _new_ inhabitant with a 
 different age will need to have knowledge of the country over it, the 
 planet ..and so on up to the universe...as i need to update all these 
 structures to reflect the change. This is pretty bad and most probably 
 doesn't need to be like this.
 
 So here I am hoping for you all to give me some pointers on how this is 
 done the functional way.
 

Nope, its not done like that. You share as much of the original
structure as you can, as a general principle.

Imagine updating a node in a tree by just detaching and reattaching a
pointer.

[1] [1]
/ \ / \
  [2] [3] update node 5   [2] [3] 
   / \ with value 7   / \
 [4] [5] [4] *

and share the rest of the structure. Since the rest isn't mutable
anyway, you can share all over.

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Phlex



Donald Bruce Stewart wrote:

Phlex:
  
On the other side, using the functional paradigm, it seems to me that 
the function i use in order to create a _new_ inhabitant with a 
different age will need to have knowledge of the country over it, the 
planet ..and so on up to the universe...as i need to update all these 
structures to reflect the change. This is pretty bad and most probably 
doesn't need to be like this.


Nope, its not done like that. You share as much of the original
structure as you can, as a general principle.

Imagine updating a node in a tree by just detaching and reattaching a
pointer.

[1] [1]
/ \ / \
  [2] [3] update node 5   [2] [3] 
   / \ with value 7   / \

 [4] [5] [4] *

and share the rest of the structure. Since the rest isn't mutable
anyway, you can share all over.

-- Don


That's precisely the thing i don't understand.
In order to update node 3 with a new pointer, i need to mutate it, so i 
need to recreate it, and so on up to node 1.


Now in this exemple, it's ok since that's a regular tree and the process 
can be automated, but when each node has a different type, it can become 
quite hairy.


Sacha

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Phlex



Bulat Ziganshin wrote:

Hello Phlex,

Sunday, June 3, 2007, 11:41:29 AM, you wrote:
  

That's precisely the thing i don't understand.
In order to update node 3 with a new pointer, i need to mutate it, so i
need to recreate it, and so on up to node 1.



yes, that's true

  

Now in this exemple, it's ok since that's a regular tree and the process
can be automated, but when each node has a different type, it can become
quite hairy.



may be all that you need is structure update syntax?

data Planet = Planet { age :: Double
 , weight :: Double
 .
 }

updatePlanet p = p {age=(age p)*2}


  


The thing is, now that i have my planet p... i want to change it's age 
... and get back the new state of the universe...


So i need to do something like this :

changePlanetAge universe galaxy planet age = ...lots of code, returning 
a new universe
And the same code for all functions updating any of the properties of my 
planet ...
And the same code for all functions updating properties of a country on 
this planet...


while in the OO paradigm, i only need to do

changlePlanetAge planet age = ...just what you wrote

I understand that the advantages of functional programming do come at a 
cost ... And i'm pretty sure you guys came up with some way to avoid 
expressing all that upward copying, although it must happen somehow.


I'm not sure i'm being clear here.

Carkos


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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Malcolm Wallace
Phlex [EMAIL PROTECTED] writes:

 The thing is, now that i have my planet p... i want to change it's age 
 ... and get back the new state of the universe...

It is true, there is often a significant amount of boilerplate code
needed to wrap a simple planet-change nested deep within a universe
structure.

There has been lots of research into easing the pain of creating this
outer traversal code - search for Scrap your boilerplate, compos,
Play, generic traversal (in conjunction with Haskell).

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Tillmann Rendel

Hello,

Phlex wrote:
changePlanetAge universe galaxy planet age = ...lots of code, returning 
a new universe
And the same code for all functions updating any of the properties of my 
planet ...
And the same code for all functions updating properties of a country on 
this planet...


In functional programming, problems of the kind and the same code for 
all functions doing something related are most often solved by 
introducing higher order functions. Let's try to decompose the problem 
as follows:


(1) change an attribute
(2) change a planet by changing one of it's attributes
(3) change a galaxy by changing one of it's planets
(4) change an universe by changing one of it's galaxies.

(1) is done by functions of type (Attribute - Attribute). We will 
construct them on the fly.


For (2), we need functions for each attribute of a planet.

  type Name = String
  type Age = Integer
  data Planet = Planet Name Age

  -- lift name changer to planet changer
  changeName :: (Name - Name) - Planet - Planet
  changeName f (Planet n a) = Planet (f n) a

  -- lift age changer to planet changer
  changeAge :: (Age - Age) - Planet - Planet
  changeAge f (Planet n a) = Planet n (f a)

we need one of these functions for each attribute of each object. they 
correspond to setter-Methods in oop.


For (3), we have to select one of the planets in a galaxy to be changed. 
Let's assume integer indices for all planets.


  type Galaxy = [Planet]

  -- lift planet changer to galaxy changer
  changePlanet :: Integer - (Planet - Planet) - Galaxy - Galaxy
  changePlanet 0 f (p:ps) = f p : ps
  changePlanet n f (p:ps) = p : changePlanet (pred n) f ps

For (4), we have to select one of the galaxies in a universe to be 
changed. Let's assume integer indices again.


  type Universe = [Galaxy]

  -- lift galaxy changer to universe changer
  changeGalaxy :: Integer - (Galaxy - Galaxy) - Universe - Universe
  changeGalaxy 0 f (g:gs) = f g : gs
  changeGalaxy n f (g:gs) = g : changeGalaxy (pred n) f gs

Oups, that's the same as (3), up to renaming of types and variables. 
Let's refactor it to


  -- lift element changer to list changer
  changeElement :: Integer - (a - a) - [a] - [a]
  changeElement f 0 (x:xs) = f x : xs
  changeElement f n (x:xs) = x : changeListElement f (pred n) xs

  -- provide nicer names
  changePlanet = changeElement
  changeGalaxy = changeElement

Let's see how we can use this:

To set the name of the second planet of the third galaxy to earth:

  (changeGalaxy 2 $ changePlanet 1 $ changeName $ const earth) univ

To increase the age of the same planet by 1:

  (changeGalaxy 2 $ changePlanet 1 $ changeAge $ succ) univ

Using map instead of changeElement, we can change all galaxies or 
planets at once:


  --  provide nicer names
  changeGalaxies = map
  changePlanets = map

To set the name of the first planet in all galaxies to first:

  (changeGalaxies $ changePlanet 0 $ changeName $ const first) univ

To increase the age of all planets by one:

  (changeGalaxies $ changePlanets $ changeAge $ succ) univ

A possible next step is to use typeclasses as supposed by apfelmus to 
access elements of different structures in a uniform way.


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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Phlex



Tillmann Rendel wrote:

Hello,

Phlex wrote:
changePlanetAge universe galaxy planet age = ...lots of code, 
returning a new universe
And the same code for all functions updating any of the properties of 
my planet ...
And the same code for all functions updating properties of a country 
on this planet...


In functional programming, problems of the kind and the same code for 
all functions doing something related are most often solved by 
introducing higher order functions. Let's try to decompose the problem 
as follows:


(1) change an attribute
(2) change a planet by changing one of it's attributes
(3) change a galaxy by changing one of it's planets
(4) change an universe by changing one of it's galaxies.

(1) is done by functions of type (Attribute - Attribute). We will 
construct them on the fly.


For (2), we need functions for each attribute of a planet.

  type Name = String
  type Age = Integer
  data Planet = Planet Name Age

  -- lift name changer to planet changer
  changeName :: (Name - Name) - Planet - Planet
  changeName f (Planet n a) = Planet (f n) a

  -- lift age changer to planet changer
  changeAge :: (Age - Age) - Planet - Planet
  changeAge f (Planet n a) = Planet n (f a)

we need one of these functions for each attribute of each object. they 
correspond to setter-Methods in oop.


For (3), we have to select one of the planets in a galaxy to be 
changed. Let's assume integer indices for all planets.


  type Galaxy = [Planet]

  -- lift planet changer to galaxy changer
  changePlanet :: Integer - (Planet - Planet) - Galaxy - Galaxy
  changePlanet 0 f (p:ps) = f p : ps
  changePlanet n f (p:ps) = p : changePlanet (pred n) f ps

For (4), we have to select one of the galaxies in a universe to be 
changed. Let's assume integer indices again.


  type Universe = [Galaxy]

  -- lift galaxy changer to universe changer
  changeGalaxy :: Integer - (Galaxy - Galaxy) - Universe - Universe
  changeGalaxy 0 f (g:gs) = f g : gs
  changeGalaxy n f (g:gs) = g : changeGalaxy (pred n) f gs

Oups, that's the same as (3), up to renaming of types and variables. 
Let's refactor it to


  -- lift element changer to list changer
  changeElement :: Integer - (a - a) - [a] - [a]
  changeElement f 0 (x:xs) = f x : xs
  changeElement f n (x:xs) = x : changeListElement f (pred n) xs

  -- provide nicer names
  changePlanet = changeElement
  changeGalaxy = changeElement

Let's see how we can use this:

To set the name of the second planet of the third galaxy to earth:

  (changeGalaxy 2 $ changePlanet 1 $ changeName $ const earth) univ

To increase the age of the same planet by 1:

  (changeGalaxy 2 $ changePlanet 1 $ changeAge $ succ) univ

Using map instead of changeElement, we can change all galaxies or 
planets at once:


  --  provide nicer names
  changeGalaxies = map
  changePlanets = map

To set the name of the first planet in all galaxies to first:

  (changeGalaxies $ changePlanet 0 $ changeName $ const first) univ

To increase the age of all planets by one:

  (changeGalaxies $ changePlanets $ changeAge $ succ) univ

A possible next step is to use typeclasses as supposed by apfelmus to 
access elements of different structures in a uniform way.


  Tillmann



This is very informative, and easier to grasp for such a newbie as me.
So the idea is to take the changing function down the chain, i knew 
this couldn't be that hard !
Still this requires indeed to think different, I guess i'm up for quite 
a few exercises in order to wrap my mind around this.


That's the kind of information that's missing from all these tutorials i 
found around the web.


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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Claus Reinke

hi there,


Let's say i have a deep nested data structure.
Universe containing galaxies, containing solar systems, containing 
planets, containing countries, containing inhabitants, containing 
...whatever.


Using the OO paradigm, once i get a reference to an inhabitant, i can 
update it quite easily (say by changing it's age), and that's the end of it.


but that approach limits you to about one choice for modelling your 
problem: a big ball of interlinked updateable references. every time

you update anything, you update everything, because that is all there is.
so you've reached the end of it for your modelling process before
you've even started to think about how best to model your problem.

haskell does have updateable references, so you could replicate that
approach, though i'd suspect there'd be very few cases where this
could actually be recommended. so here are two alternative, related
approaches, to give you an idea of what is possible:

data Universe = U [Galaxy] deriving Show
data Galaxy = G [SolarSystem] deriving Show
data SolarSystem = S [Planet] deriving Show
type Planet = String

u = U [G [S [mercury,venus,earth,mars]]] -- it's a small world

a) work inside the outer structures, by moving the work inwards, 
   to the target


traverseU g traverse (U gs) = U (here++(traverse this:there))
   where (here,this:there) = splitAt g gs
traverseG s traverse (G ss) = G (here++(traverse this:there))
   where (here,this:there) = splitAt s ss
traverseS p traverse (S ps) = S (here++(traverse this:there))
   where (here,this:there) = splitAt p ps

so, to work on a planet, you'd visit its solar system, then do the
work there:

workOnPlanet [g,s,p] work = traverseU g (traverseG s (traverseS p work))

b) work through the outer structures, by lifting target accessors 
outwards


liftUget g get (U gs) = get (gs!!g)
liftGget s get (G ss) = get (ss!!s)
liftSget p get (S ps) = get (ps!!p)

liftUset g set (U gs) =  U (here++(set this:there))
   where (here,this:there) = splitAt g gs
liftGset s set (G ss) =  G (here++(set this:there))
   where (here,this:there) = splitAt s ss
liftSset p set (S ps) =  S (here++(set this:there))
   where (here,this:there) = splitAt p ps

getPlanet get [g,s,p] = liftUget g (liftGget s (liftSget p get))
setPlanet set [g,s,p] = liftUset g (liftGset s (liftSset p set))

now, if 'get'/'set' work on a planet, then 'getPlanet get [g,s,p]'/
'setPlanet set [g,s,p]' work on a specific planet in a universe.

main = do
 print $ workOnPlanet [0,0,2] (HERE: ++) u
 print $ getPlanet id [0,0,2] u
 print $ setPlanet (const EARTH) [0,0,2] u

while (b) may be closer to the 'reference into everything' you're used
to, (a) is usually nicer and more efficient, because it nests larger chunks
of work instead of nesting each and every small step. both styles are in 
common use in haskell, though getset are often merged into one.


there are more interesting aspects to this, eg, how exactly to model
the data structures (lists are a useable default, but not always the best
choice), or how to share substructures not affected by updates, or 
how to make traversal more flexible, so that we can change traversal
directions on the fly, or how to extract the commonalities in the data 
structure interfaces, so that we only have to write that traverse or 
lifting code once, and perhaps generically over the different types
addressed by different paths, etc. but since all of those will no 
doubt be addressed in other replies, i thought a simple start might 
be best;-)


hth,
claus

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Felipe Almeida Lessa

On 6/3/07, Tillmann Rendel [EMAIL PROTECTED] wrote:

In functional programming, problems of the kind and the same code for
all functions doing something related are most often solved by
introducing higher order functions. Let's try to decompose the problem
as follows:

[snip]

Now I've got one question ;).  Is it *efficient* to go down this way?
You are recreating (parts of) two lists and checking every planet,
every time you need to change something. Maybe using a Map instead of
a list would at least let the complexity go down a little bit? Or am I
missing something?

Cheers, =)

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Vincent Kraeutler
Phlex wrote:
 This is very informative, and easier to grasp for such a newbie as me.
 So the idea is to take the changing function down the chain, i knew
 this couldn't be that hard !
 Still this requires indeed to think different, I guess i'm up for
 quite a few exercises in order to wrap my mind around this.

 That's the kind of information that's missing from all these tutorials
 i found around the web.

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



for what it's worth, i find it easiest to think about it this way:

assume you want to update a planet, i.e. you want to apply
changeP :: Planet - Planet
to one planet in your system.

the important step is then to invoke wishful thinking (viz. SICP), and
assume you can partition your data structure into two parts, the one
that stays constant, and the one that is changed, i.e.

partition :: Universe - (Rest, Planet)

with a corresponding inverse operation

recombine :: (Rest, Planet) - Universe

So after the partitioning, updating the planet of interest is very easy
to accomplish:

changeP' (rest, planet) = (rest, changeP planet)

rolling the partitioning, updating and recombination into one, we get

update u = recombine (changeP' (partition u))

The second step is then to find out how to do the partitioning and
recombination easily and efficiently. For one very generic way to do
this, i would recommend that you read up on the Zipper data structure [1-3].

kind regards,
v.

[1] http://en.wikibooks.org/wiki/Haskell/Zippers
[2]
http://www.st.cs.uni-sb.de/edu/seminare/2005/advanced-fp/docs/huet-zipper.pdf
[3] http://cgi.cse.unsw.edu.au/~dons/blog/2007/05/17#xmonad_part1b_zipper





signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Ketil Malde
On Sun, 2007-06-03 at 09:02 -0300, Felipe Almeida Lessa wrote:
 On 6/3/07, Tillmann Rendel [EMAIL PROTECTED] wrote:
  In functional programming, problems of the kind and the same code for
  all functions doing something related are most often solved by
  introducing higher order functions. Let's try to decompose the problem
  as follows:

 Now I've got one question ;).  Is it *efficient* to go down this way?

Only one way to find out!

 Maybe using a Map instead of
 a list would at least let the complexity go down a little bit? Or am I
 missing something?

I was going to suggest that.  The difference - well, one of them -
between OOP and FP is that FP deals with values, OOP with data ojects.
The objects have identity, so you can change the name of a planet, and
maintain that it is still the same planet.  A value is just defined as
itself, and if you insist you can change a value, at least you must
admit it then becomes a different one.

Identity can be emulated by relatively straightforward means: store all
planets in a Map indexed by something that is useful as an identifier
(i.e. stays constant and is unique), and have a Galaxy keep a list of
identifiers.

You may even find that the dissociation of galaxies from planets etc is
an advantage, perhaps you want to deal with planets irrespectively of
their galaxies, or perhaps some planets don't even belong to a galaxy?

-k


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