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

2007-06-06 Thread Jean-Marie Gaillourdet

Hi,

On 06.06.2007, at 07:00, Phlex wrote:

So here is one more question :

Let's say I want unique System names across the Universe ... that  
would mean i need to have a Data.Map in the Universe, with Name  
keys and System values. Since all data are values instead of  
references, would i end up with two copies of each System (in  
Universe's Data.Map and in its Galaxy), or would these be shared  
somehow ? In other words, should i go for integer (or maybe access  
key/tuple) identified objects or just put the System in both  
Data.Maps it belongs to ?


That depends. In an OO world everything has its own implicit  
identity. The new operator in Java provides you with an object with a  
new and unique key which is not easy to observe. But most formal  
semantics have it. One can think of it as the address of the  
allocated object.


In FP there are no objects, there are only terms. Whether two terms  
are identically is answered by a structural traversal over the values  
and subvalues.


Now, I return to your question. What makes your objects galaxies,  
planets, stars, etc. unique? Is it their coordinate in space, their  
name, their structural position in your tree? What is it? Let's  
assume you say their names are unique. Then you only have to store a  
set of all names used in your universe.


If you want a planet which orbits around star a to be different  
form another planet that is in orbit of star b, although both  
planets are the same in every other aspect. Then you might think  
about introducing arbitrary unique integer keys.


This is similar to database design. There are those normal form laws  
[1] which guide you to improve your db schema. In database design  
there are people who introduce artificial primary keys almost always.  
Although there are natural primary keys most of the time.


I hope these random thoughts help a bit to change the perspective.

Regards,
  Jean-Marie

[1] http://en.wikipedia.org/wiki/Database_normalization
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-06-05 Thread Phlex



Christopher Lane Hinson wrote:


Where InsidenessMap a b c represents a relationship where b's are 
inside a's, and b's have a state of c.  Then, you need to declare a 
separate InsidenessMap for each possible relationship, but this 
ensures that you'll never put a galaxy inside a solar system.  Or you 
can make 'a' be a reference to any type of object; there are options.




Ketil Malde wrote:

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.
  


So basically you guys are saying I should rethink the data structure 
into a relational model instead of sticking to the OO model... I think i 
could do this pretty easily. a table would be a map of id to instance 
...then another map for foreign keys, or maybe just as a member of each data


Is the relational model a better fit than the object model for 
functional programming ?


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


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

2007-06-05 Thread Al Falloon

Phlex wrote:



Christopher Lane Hinson wrote:


Where InsidenessMap a b c represents a relationship where b's are 
inside a's, and b's have a state of c.  Then, you need to declare a 
separate InsidenessMap for each possible relationship, but this 
ensures that you'll never put a galaxy inside a solar system.  Or you 
can make 'a' be a reference to any type of object; there are options.




Ketil Malde wrote:

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.
  


So basically you guys are saying I should rethink the data structure 
into a relational model instead of sticking to the OO model... I think i 
could do this pretty easily. a table would be a map of id to instance 
...then another map for foreign keys, or maybe just as a member of each 
data


Is the relational model a better fit than the object model for 
functional programming ?


Of course it depends on what you are doing, but I actually have never 
needed to encode a relational model like this, even when I have deeply 
nested structures.


I find that my usual solution involves doing my transformations on the 
data structure all at once. By that I mean that instead of performing 
a number of steps from the root of the data structure, I do all the 
operations in one pass.


To keep the algorithms decoupled I usually end up passing the operations 
to perform as an argument. Higher-order functions are your friend.


Because Haskell is lazy I don't really worry about doing too much and 
if I really need it, I can use the result as part of the transformation 
(its like recursion, but with values). Between laziness and HOF I rarely 
need any kind of state.


Its not directly related to your question, but I found the iterative 
root-finding and differentiation examples in Why Functional Programming 
Matters [1] to be eye-opening about the functional way because they 
are algorithms that are almost always described as stateful 
computations, but are shown to be very elegant in a pure functional 
implementation.


[1] http://www.math.chalmers.se/~rjmh/Papers/whyfp.html

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


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

2007-06-05 Thread apfelmus
Phlex wrote:
 Ketil Malde wrote:
 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.
   
 
 So basically you guys are saying I should rethink the data structure
 into a relational model instead of sticking to the OO model... I think i
 could do this pretty easily. a table would be a map of id to instance
 then another map for foreign keys, or maybe just as a member of each
 data
 
 Is the relational model a better fit than the object model for
 functional programming ?

Well, not really. I mean, if the problem is indeed to store all known
planets in the universe, then it's indeed a database in nature and you
have to support fine grained operations like

   delete :: Key - Database - Database
   insert :: Key - Item - Database - Database
   ... and so on ...

(Note that some proposals like

  changeGalaxies $ changePlanet 0 $ changeName $ const first

or functional references can be interpreted as keys for 'insert' or
'delete'. I mean that this expression already is the key to look up a
planet inside the universe, it's just that this key has a rather unusual
type. And that you can compose keys.)

But if the problem at hand is perhaps a binary search tree or some other
data structure, you can implement many operations without using
per-element 'delete' or 'insert' although every operation can in
principle be built up from those. Maybe it helps if you elaborate on
your concrete problem?

Regards,
apfelmus

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


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

2007-06-05 Thread Phlex



apfelmus wrote:

Phlex wrote:
  

Ketil Malde wrote:

Is the relational model a better fit than the object model for

functional programming ?



Well, not really. I mean, if the problem is indeed to store all known
planets in the universe, then it's indeed a database in nature and you
have to support fine grained operations like

   delete :: Key - Database - Database
   insert :: Key - Item - Database - Database
   ... and so on ...

(Note that some proposals like

  changeGalaxies $ changePlanet 0 $ changeName $ const first

or functional references can be interpreted as keys for 'insert' or
'delete'. I mean that this expression already is the key to look up a
planet inside the universe, it's just that this key has a rather unusual
type. And that you can compose keys.)

But if the problem at hand is perhaps a binary search tree or some other
data structure, you can implement many operations without using
per-element 'delete' or 'insert' although every operation can in
principle be built up from those. Maybe it helps if you elaborate on
your concrete problem?

Regards,
apfelmus
  
Well the current state of my haskell knowledge doesn't allow any kind of 
serious work, so I'm indeed currently playing with Universe, Galaxies, 
Systems, Planets and Moons =P. I'm an application programmer, and i 
thought that if I can model a moving universe (a small one though!), I 
guess i'll be one step closer to translating this knowledge to building 
statefull server applications.


I'm worried that my OO view of things might interfere with the haskell 
ways. So yes, what i'm looking for right now is more of a high level 
how-to, and that's precisely what you guys provided to me. Thanks for 
that !


So here is one more question :

Let's say I want unique System names across the Universe ... that would 
mean i need to have a Data.Map in the Universe, with Name keys and 
System values. Since all data are values instead of references, would i 
end up with two copies of each System (in Universe's Data.Map and in its 
Galaxy), or would these be shared somehow ? In other words, should i go 
for integer (or maybe access key/tuple) identified objects or just put 
the System in both Data.Maps it belongs to ?


regards,
Sacha




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


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

2007-06-04 Thread David Menendez
Arie Peterson writes:

 There are two things one typically wants to do when working with a
 substructure of some larger data structure: (1) extract the
 substructure; and (2) change the larger structure by acting on the
 substructure. A 'Ref cx t' encodes both of these functions (for a
 substructure of type 't' and larger structure (context) of type 'cx').
 
  data Ref cx t
   = Ref
 {
   select :: cx - t
 , update :: (t - t) - cx - cx
 }
 
 A Ref is a bit like a typed and composable incarnation of apfelmus's
 indices, or a wrapper around Tillmann's change* functions, containing
 not only a setter but also the accompanying getter.

That's a neat idiom. I wonder how far one could usefully generalize it.

For example,

type Ref cx t = forall f. Functor f = (t - f t) - cx - f cx

newtype Id a = Id { unId :: a }
instance Functor Id where fmap f = Id . f . unId

newtype K t a = K { unK :: t }
instance Functor (K t) where fmap = K . unK


select :: Ref cx t - cx - t
select ref = unK . ref K

update :: Ref cx t - (t - t) - cx - cx
update ref f = unId . ref (Id . f)


rfst :: Ref (a,b) a
rfst f (x,y) = fmap (\x' - (x',y)) (f x)

In this implementation, composition of Refs is just function
composition.

select (rfst . rfst) :: ((a,b),c) - a
-- 
David Menendez [EMAIL PROTECTED] | In this house, we obey the laws
http://www.eyrie.org/~zednenem  |of thermodynamics!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2007-06-04 Thread Claus Reinke

|  data Ref cx t
|   = Ref
| {
|   select :: cx - t
| , update :: (t - t) - cx - cx
| }
| 
| A Ref is a bit like a typed and composable incarnation of apfelmus's

| indices, or a wrapper around Tillmann's change* functions, containing
| not only a setter but also the accompanying getter.
|
|That's a neat idiom. I wonder how far one could usefully generalize it.

you might find Koji Kagawa's papers interesting:

http://guppy.eng.kagawa-u.ac.jp/~kagawa/publication/index-e.html

in particular

Mutable Data Structures and Composable References 
in a Pure Functional Language , Koji Kagawa, In SIPL '95: 
State in Programming Languages, San Francisco, USA, January 1995.


Compositional References for Stateful Functional Programming, 
Koji Kagawa, ICFP 1997, June 1997, Amsterdam, the Netherlands. 


claus

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


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

2007-06-04 Thread Arie Peterson
David Menendez wrote:

| That's a neat idiom. I wonder how far one could usefully generalize it.
|
| For example,
|
| type Ref cx t = forall f. Functor f = (t - f t) - cx - f cx
|
| newtype Id a = Id { unId :: a }
| instance Functor Id where fmap f = Id . f . unId
|
| newtype K t a = K { unK :: t }
| instance Functor (K t) where fmap = K . unK
|
|
| select :: Ref cx t - cx - t
|select ref = unK . ref K
|
| update :: Ref cx t - (t - t) - cx - cx
| update ref f = unId . ref (Id . f)
|
|
| rfst :: Ref (a,b) a
| rfst f (x,y) = fmap (\x' - (x',y)) (f x)
|
| In this implementation, composition of Refs is just function
| composition.
|
| select (rfst . rfst) :: ((a,b),c) - a

Cool!

Reversely, you can usefully convert my Refs to yours:

fRef :: Original.Ref cx t - David.Ref cx t
fRef r h cx = fmap (($ cx) . update r . const) $ h (select r cx)


Claus Reinke wrote:

| you might find Koji Kagawa's papers interesting:
|
| [...]

Mm, more reading... :-)


Greetings,

Arie

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


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

2007-06-03 Thread apfelmus
Phlex wrote:
 Donald Bruce Stewart wrote:

 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.
 
 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 correct, I think Dons shared a bit too much here :)

[1]   [1']
/ \   /  \
  [2] [3]  update node 5[2]  [3']
  / \/  \
[4] [5][4]  [5']

You have to recreate all nodes that point directly or indirectly to 5,
but you can share all the other nodes like 2 and 4 that have no forward
pointers to 5.

Note that creating new nodes is dead simple, there's no effort involved
on the programmer's part. Here's an example that rotates the top of a
binary tree:

  data Tree a = Leaf a | Node (Tree a) (Tree a)

  rotateRight :: Tree a - Tree a
  rotateRight (Node (Node a b) c) = Node a (Node b c)

The top two nodes are recreated with the constructor Node but a,b and c
are shared.

 Now in this example, 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.

Yes and no. The point is that if you can't automate it, you have to code
it by hand anyway which constitutes most of the hairiness. But I know
what you mean and there's a nice way to do that with multi-parameter
type classes.

Let's assume a data structure

  data Universe = Universe [Galaxy]
  data Galaxy   = Galaxy   [Planet]
  data Planet   = Planet   { name :: String, size :: Double }

The insight is that in order to reference a planet inside the universe
structure, you have to know the path from the top. In other words, you
have to know that's it's the 2nd planet from the 4th galaxy before you
look up its name. If you don't throw that information away, you can use
it to update it as well. In effect, the Universe behaves like a finite
map with composite keys.

  {-# OPTIONS_GHC -fglasgow-exts -#}
  import Prelude hiding (lookup)

  class Map map key a | map key - a where
  lookup :: key - map - Maybe a
  adjust :: (a - a) - key - map - map

  instance Map [a] Int a where
  lookup 0 [x]= Just x
  lookup 0 _  = Nothing
  lookup k (x:xs) = lookup (k-1) xs
  lookup _ _  = Nothing

  adjust f 0 [x]= [f x]
  adjust _ 0 xs = error Index out of range
  adjust f k (x:xs) = x : adjust f (k-1) xs
  adjust f _ xs = error Index out of range

  instance Map Universe Int Galaxy where
  lookup k (Universe gs)   = lookup k gs
  adjust f k (Universe gs) = Universe (adjust f k gs)

  instance Map Galaxy Int Planet where
  lookup k (Galaxy ps)   = lookup k ps
  adjust f k (Galaxy ps) = Galaxy (adjust f k ps)

  instance (Map m k m', Map m' k' a) = Map m (k,k') a where
  lookup (k,k') m   = lookup k m = lookup k'
  adjust f (k,k') m = adjust (adjust f k') k m


You can lookup the 2nd planet in the 4th galaxy with

  lookup (4,2) universe :: Maybe Planet

and you can update it via

  adjust (\planet - planet {name = Earth}) (4,2) universe

Thanks to type-classes and overloading, you can still access single
galaxies with

  lookup 4 universe :: Maybe Galaxy



Regards,
apfelmus

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


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

2007-06-03 Thread Donald Bruce Stewart
apfelmus:
 Phlex wrote:
  Donald Bruce Stewart wrote:
 
  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.
  
  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 correct, I think Dons shared a bit too much here :)

Spent too much time with zippers lately ;)

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


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

2007-06-03 Thread Phlex

apfelmus wrote:

Phlex wrote:
  

Donald Bruce Stewart wrote:


Yes and no. The point is that if you can't automate it, you have to code
it by hand anyway which constitutes most of the hairiness. But I know
what you mean and there's a nice way to do that with multi-parameter
type classes.

Let's assume a data structure

  data Universe = Universe [Galaxy]
  data Galaxy   = Galaxy   [Planet]
  data Planet   = Planet   { name :: String, size :: Double }

The insight is that in order to reference a planet inside the universe
structure, you have to know the path from the top. In other words, you
have to know that's it's the 2nd planet from the 4th galaxy before you
look up its name. If you don't throw that information away, you can use
it to update it as well. In effect, the Universe behaves like a finite
map with composite keys.

  {-# OPTIONS_GHC -fglasgow-exts -#}
  import Prelude hiding (lookup)

  class Map map key a | map key - a where
  lookup :: key - map - Maybe a
  adjust :: (a - a) - key - map - map

  instance Map [a] Int a where
  lookup 0 [x]= Just x
  lookup 0 _  = Nothing
  lookup k (x:xs) = lookup (k-1) xs
  lookup _ _  = Nothing

  adjust f 0 [x]= [f x]
  adjust _ 0 xs = error Index out of range
  adjust f k (x:xs) = x : adjust f (k-1) xs
  adjust f _ xs = error Index out of range

  instance Map Universe Int Galaxy where
  lookup k (Universe gs)   = lookup k gs
  adjust f k (Universe gs) = Universe (adjust f k gs)

  instance Map Galaxy Int Planet where
  lookup k (Galaxy ps)   = lookup k ps
  adjust f k (Galaxy ps) = Galaxy (adjust f k ps)

  instance (Map m k m', Map m' k' a) = Map m (k,k') a where
  lookup (k,k') m   = lookup k m = lookup k'
  adjust f (k,k') m = adjust (adjust f k') k m


You can lookup the 2nd planet in the 4th galaxy with

  lookup (4,2) universe :: Maybe Planet

and you can update it via

  adjust (\planet - planet {name = Earth}) (4,2) universe

Thanks to type-classes and overloading, you can still access single
galaxies with

  lookup 4 universe :: Maybe Galaxy

Regards,
apfelmus


This answers precisely my question.
Hiding the access/update methods behind a common interface, that's the 
key ...


Thanks a lot,
Sacha


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


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

2007-06-03 Thread apfelmus
apfelmus wrote:
   {-# OPTIONS_GHC -fglasgow-exts -#}
   import Prelude hiding (lookup)
 
   class Map map key a | map key - a where
   lookup :: key - map - Maybe a
   adjust :: (a - a) - key - map - map
 
   instance (Map m k m', Map m' k' a) = Map m (k,k') a where
   lookup (k,k') m   = lookup k m = lookup k'
   adjust f (k,k') m = adjust (adjust f k') k m

Uh, that actually needs -fundecidable-instances or something similar.
Using explicit functor composition doesn't resolve the problem

  class Map map key | map - key where
 lookup :: key - map a - Maybe a
 adjust :: (a - a) - key - map a - map a

  data O f g a = O (f (g a))

  instance (Map m k, Map m' k') = Map (m `O` m') (k,k') a where
...

  -- but how to make ((m `O` m') a) a map for (m' a)?

With associated type synonyms, this program can't even be formulated.
Any ideas?


For the time being, you can specialize the key-pairing for concrete maps
in question.

  newtype UniverseF a = UniverseF [a]
  newtype GalaxyF   a = GalaxyF [a]

  type Universe   = UniverseF Galaxy
  type Galaxy = GalaxyF Planet
  data Planet = ...

  instance Map (UniverseF a) k a where ...
  instance Map m k a = Map (UniverseF m) (Int,k) a where ...

Oh, and you need a dummy instance for Planets as singleton-maps.

  instance Map Planet () Planet where ...

Regards,
apfelmus

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


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

2007-06-03 Thread Christopher Lane Hinson



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


Oh.  I had /exactly/ this problem.  If you use separate types (i.e. a 
newtyped integer, acting kindof like a pointer) to represent (1) the 
identity and (2) the state of the object, you can use a separate data 
structure that remembers which object is inside which other object.


http://www.downstairspeople.org/darcs/unstable/roguestar-engine/src/InsidenessMap.hs

Where InsidenessMap a b c represents a relationship where b's are inside 
a's, and b's have a state of c.  Then, you need to declare a separate 
InsidenessMap for each possible relationship, but this ensures that you'll 
never put a galaxy inside a solar system.  Or you can make 'a' be a 
reference to any type of object; there are options.


But, you just update this structure once, with no thought of recursively 
updating a heterogenous tree of data.


It may not be the best solution, but if I knew of something better I
would be using the better thing instead.

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


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

2007-06-03 Thread Arie Peterson
You could also use 'compositional functional references'. These are
introduced in the paper A Functional Programming Technique for Forms in
Graphical User Interfaces by Sander Evers, Peter Achten and Jan Kuper.

=== Introduction ===

There are two things one typically wants to do when working with a
substructure of some larger data structure: (1) extract the substructure;
and (2) change the larger structure by acting on the substructure. A 'Ref
cx t' encodes both of these functions (for a substructure of type 't' and
larger structure (context) of type 'cx').

 data Ref cx t
  = Ref
{
  select :: cx - t
, update :: (t - t) - cx - cx
}

A Ref is a bit like a typed and composable incarnation of apfelmus's
indices, or a wrapper around Tillmann's change* functions, containing not
only a setter but also the accompanying getter.

=== Use ===

These Refs are compositional: given 'x :: Ref a b' and 'y :: Ref b c', we
can form

 z :: Ref a c
 z = Ref
 {
   select = select b . select a
 , update = update a . update b
 }

. In fact we can almost make 'Ref' into an arrow. (Only 'pure :: (a - b)
- Ref a b' does not make sense, because a pure function 'f : a - b'
doesn't give information about how to transform a change in 'b' into a
change in 'a'.)

I've written a template haskell function to derive Refs from a data
structure definition (with record syntax): given

 data Universe
   = Universe
 {
   galaxies :: [Galaxy]
 }

, it creates

 galaxiesRef :: Ref Universe [Galaxy]

. Together with some Ref functions for container types (List, Map, etc.)
this eliminates most (all?) necessary boilerplate code.


Greetings,

Arie

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


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

2007-06-03 Thread Stefan O'Rear
(Sorry to break the thread, but mutt somehow managed to eat the message
I'm replying to...)

Arie Peterson:
 You could also use 'compositional functional references'. These are
 introduced in the paper A Functional Programming Technique for Forms in
 Graphical User Interfaces by Sander Evers, Peter Achten and Jan Kuper.

 === Introduction ===

 There are two things one typically wants to do when working with a
 substructure of some larger data structure: (1) extract the substructure;
 and (2) change the larger structure by acting on the substructure. A 'Ref
 cx t' encodes both of these functions (for a substructure of type 't' and
 larger structure (context) of type 'cx').

  data Ref cx t
   = Ref
 {
   select :: cx - t
 , update :: (t - t) - cx - cx
 }
...
 I've written a template haskell function to derive Refs from a data   
   
structure definition 
 (with record syntax): given

I've implemented this in Derive[1] in 12 minutes, counting the time
required to re-familiarize with the code.  The patch is at [2] and has
also been darcs sent.

[1] http://www-users.cs.york.ac.uk/~ndm/derive
[2] http://members.cox.net/stefanor/derive-Ref-patch

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


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

2007-06-03 Thread Neil Mitchell

Hi


 You could also use 'compositional functional references'. These are
 introduced in the paper A Functional Programming Technique for Forms in
 Graphical User Interfaces by Sander Evers, Peter Achten and Jan Kuper.

 I've written a template haskell function to derive Refs from a data  
  
structure definition (with record 
syntax): given

I've implemented this in Derive[1] in 12 minutes, counting the time
required to re-familiarize with the code.  The patch is at [2] and has
also been darcs sent.

[1] http://www-users.cs.york.ac.uk/~ndm/derive


It's been applied, and is now in the main repo.

Thanks

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