doubly linked list

2000-04-27 Thread Jan Brosius



Hi,
 
I wonder if it is possible to simulate a doubly linked list in 
Haskell.
 
Friendly
 
Jan Brosius


doubly linked list

2000-04-27 Thread Frank Atanassow

Jan Brosius writes:
 > I wonder if it is possible to simulate a doubly linked list in Haskell.

Interesting question. Usually you don't need any kind of "double-linkedness"
because there are no imperative effects, but sometimes it is useful to
simulate something analogous. The idea is to treat "locations" in a list
rather than the list as a whole, a location in xs being some tail of xs; this
is done indirectly by modelling the context as a path from the start of the
list, along with the elements contained along the path.

 type Loc a = ([a],[a])

 first xs = ([],xs)
 last xs = (reverse xs, [])

 next (ys,x:xs) = (x:ys,xs)
 back (y:ys,xs) = (ys,y:xs)

So you see, for a list, the context of a location happens to be representable
as another list, with its elements reversed. However, this idea can be
generalized to arbitrary first-order datatypes, and in general the contexts
aren't isomorphic to the datatype in question. For example, suppose we have a
binary tree:

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

Its contexts look like this

  data Cxt a = Top | L (Cxt a) (Tree a) | R (Tree a) (Cxt a)

and a location, as usual, is

  type Loc a = (Cxt a, Tree a)

with navigation functions like

  top t = (Top, t)
  left (c, Fork l r) = (L c r, l)
  right (c, Fork l r) = (R l c, r)

  up (L c r, l) = (c, Fork l r)
  up (R l c, r) = (c, Fork l r)

Gerard Huet published an article about this technique, which he called "The
Zipper" because of the way it inverts a data structure as you descend into it,
in the Journal of Functional Programming (I think in 1998, but I'm too lazy to
check).

Incidentally, one way to make use of this is to elaborate the context by
adding some state which depends on the location. For example, for trees you
could keep track of the depth; for terms, the free variables; etc.

However, although I think this is a neat trick, I admit I have not found much
use for it in Haskell programs. For example, one problem is that the
navigation functions are necessarily partial. It would be nicer in a language
with some subtyping or something which could ensure that you can only use,
say, "left" when you're not at a leaf. Another issue is that if you use the
contexts to track state, you really want some kind of inheritance to be able
to quickly define variants of the context datatype and its associated
functions.

In short, what you want is an OO language. For Haskell, using monads or arrows
to keep track of the computation state is more appropriate, I think.

-- 
Frank Atanassow, Dept. of Computer Science, Utrecht University
Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands
Tel +31 (030) 253-1012, Fax +31 (030) 251-3791





Re: doubly linked list

2000-04-27 Thread Keith Wansbrough

> I wonder if it is possible to simulate a doubly linked list in Haskell.

No need to simulate it... it's perfectly possible.  See my Wiki article.

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::






Re: doubly linked list

2000-04-27 Thread Chris Okasaki

> I wonder if it is possible to simulate a doubly linked list in
> Haskell.

Depends on what you mean.  

  - Using mutable state in a monad you can implement a doubly 
linked list directly.
  - If you store all the nodes of the doubly linked list in
an array and simulate the pointers with indices into the
array, then you can easily implement this in Haskell using
some kind of extensible persistent array (probably some flavor 
of binary tree).  [Here you get a logarithmic slowdown
compared to ordinary doubly linked lists.]
  - If you want to be able to add/remove things from the front/back
plus be able to splice two lists together, see my implementation
of catenable deques (ICFP'97 or in my book).
  - If you also want to be able to have a "cursor" into the middle
of the list where you can make changes, you can implement this
as a pair of catenable deques, where the first deque represents
the part before the cursor and the second deque represents the
part after the cursor.
  - If you want to allow an arbitrary number of cursors, then
the simulation using an extensible persistent array is probably
your best bet.

Chris




Re: doubly linked list

2000-04-27 Thread Keith Wansbrough

Jan Brosius wrote:

> > > I wonder if it is possible to simulate a doubly linked list 
> > in Haskell.

I wrote:

> > No need to simulate it... it's perfectly possible.  See my 
> > Wiki article.

Chris Angus wrote:

> Where is this article.
> I looked on Haskell.org to no avail

Good point!  I have no idea... it looks like the Wiki has gone AWOL.  If someone would 
tell me where my article has gone, I'd be very grateful!

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::






Re: doubly linked list

2000-04-27 Thread Jan Kort

Keith Wansbrough wrote:
> 
> 
> Good point!  I have no idea... it looks like the Wiki has gone AWOL.  If someone 
>would tell me where my article has gone, I'd be very grateful!
> 

If you find it, maybe you could put it in the "Haskell bookshelf" ?
I found very useful and Wiki has been "AWOL" for quite a while now.

Anyway, a doubly linked list could be defined like this:

data DL a
  = Node (DL a) a (DL a)
  | Empty

And the conversion from a list would look like this:

fromList :: [a] -> DL a
fromList xs = fromList2 Empty xs

fromList2 :: DL a -> [a] -> DL a
fromList2 a [] = Empty
fromList2 a (x:xs)
  = r
where
  r = Node a x s
  s = (fromList2 r xs)

Or did I make a mistake somewhere ? I still find it hard
to wrap my brain around these kind of things.

  Jan




Re: doubly linked list

2000-04-27 Thread Keith Wansbrough

Herewith the comp.lang.functional version of my article.  I may have 
tidied it up a little for the Wiki; if so, those changes are lost.  Let 
it hereby enter the Haskell List archive!




The following message is a courtesy copy of an article
that has been posted as well.

Matti Nykanen <[EMAIL PROTECTED]> writes:

> I  recently came  across an  algorithm that  constructs a  binary tree
> using single _but  not immediate_ assignments. By this  I mean that it
> attaches a newly  created node into the existing  tree, but leaves the
> children of  the totally unspecified.  Later the  algorithm returns to
> fill in the missing pieces.
> 
> I tried to  write it in Haskell,  but couldn't. If I create  a node, I
> have to give its children some  values to start with, and those cannot
> be changed later.  I don't think uniqueness types  (from, e.g., Clean)
> help here,  because the partially  constructed node is referred  to by
> two  places: its  parent in  the tree,  and the  "to do"  list  of the
> algorithm for the unfinished nodes.

The solution to this is a little trick called `tying the knot'.
Remember that Haskell is a lazy language.  A consequence of this is
that while you are building the node, you can set the children to the
final values straight away, even though you don't know them yet!  It
twists your brain a bit the first few times you do it, but it works
fine.

Here's an example (possibly topical!).  Say you want to build a
circular, doubly-linked list, given a standard Haskell list as input.
The back pointers are easy, but what about the forward ones?

data DList a = DLNode (DList a) a (DList a)

mkDList :: [a] -> DList a

mkDList [] = error "must have at least one element"
mkDList xs = let (first,last) = go last xs first
 in  first

  where go :: DList a -> [a] -> DList a -> (DList a, DList a)
go prev [] next = (next,prev)
go prev (x:xs) next = let this= DLNode prev x rest
  (rest,last) = go this xs next
  in  (this,last)

takeF :: Integer -> DList a -> [a]
takeF 0 _ = []
takeF (n+1) (DLNode _ x next) = x : (takeF n next)

takeR :: Show a => Integer -> DList a -> [a]
takeR 0 _ = []
takeR (n+1) (DLNode prev x _) = x : (takeR n prev)


(takeF and takeR are simply to let you look at the results of mkDList:
they take a specified number of elements, either forward or backward).

The trickery takes place in `go'.  `go' builds a segment of the list,
given a pointer to the node off to the left of the segment and off to
the right.  Look at the second case of `go'.  We build the first node
of the segment, using the given prev pointer for the left link, and
the node pointer we are *about* to compute in the next step for the
right link.

This goes on right the way through the segment.  But how do we manage
to create a *circular* list this way?  How can we know right at the
beginning what the pointer to the end of the list will be?

Take a look at mkDList.  Here, we simply take the (first,last)
pointers we get from `go', and *pass them back in* as the next and
prev pointers respectively, thus tying the knot.  This all works
because of lazy evaluation.

Hope this helps.

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) :
: PhD Student, Computer Laboratory, University of Cambridge, England. :
:  (and recently of the University of Glasgow, Scotland. [><] )   :
: Native of Antipodean Auckland, New Zealand: 174d47' E, 36d55' S.:
: http://www.cl.cam.ac.uk/users/kw217/  mailto:[EMAIL PROTECTED] :
:-:



-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) ---:
: PhD Student, Computer Laboratory, University of Cambridge, UK. :
: Native of Antipodean Auckland, New Zealand: 174d47'E, 36d55'S. :
: http://www.cl.cam.ac.uk/users/kw217/ mailto:[EMAIL PROTECTED] :
::





Re: doubly linked list

2000-04-27 Thread Jan Brosius


- Original Message - 
From: Chris Okasaki <[EMAIL PROTECTED]>
To: <[EMAIL PROTECTED]>
Sent: Thursday, April 27, 2000 4:13 PM
Subject: Re: doubly linked list


> > I wonder if it is possible to simulate a doubly linked list in
> > Haskell.
> 
> Depends on what you mean.  
> 
>   - Using mutable state in a monad you can implement a doubly 
> linked list directly.

please show me how to implement using mutable state in
a monad

Friendly
Jan Brosius





Re: doubly linked list

2000-04-28 Thread Jerzy Karczmarczuk

> Jan Brosius wrote:

> I wonder if it is possible to simulate a doubly linked list in
> Haskell.

... and the number of answers was impressive...

Want some more?
This is a short for *making* true double
lists, and as an extra bonus it is circular. Slightly longer than
the solution of Jan Kort, no empty lists.

A data record with three fields, the central is the value, other
are pointers.

> data Db a = Dd (Db a) a (Db a) deriving Show
-- (don't try to derive Eq...)


dlink constructs a circular list out of a standard list. Cannot
be empty. The internal fct. dble is the main iterator, which constructs
a dlist and links it at both ends to prev and foll.

> dlink ll = 
>  let (hd,lst)=dble ll lst hd
>  dble [x] prev foll = 
>let h = Dd prev x foll in (h,h)
>  dble (x:xq) prev foll =
>let h=Dd prev x nxt
>(nxt,lst) = dble xq h foll
>in (h,lst)
>  in hd

You might add some navigation utilities, e.g.

> left  (Dd a _ _) = a
> right (Dd _ _ a) = a
> val   (Dd _ x _) = x

etc. At least you don't need Monads nor Zippers. Keith Wansbrough
proposes his article. I don't know it, when you find it please
send me the references. But there are previous works, see the
article published in Software 19(2), (1989) by Lloyd Allison,
"Circular programs and self-referential structures".


Jerzy Karczmarczuk
Caen, France

PS. Oh, I see now that the KW article has been found...
Well, I send you my solution anyway.




Re: doubly linked list

2000-04-28 Thread Peter Hancock

>>>>> "Jan" == Jan Kort <[EMAIL PROTECTED]> writes:

    > Anyway, a doubly linked list could be defined like this:

That was very interesting.  It seems to generalise to put
back-pointers and other context info in a variety of data
structures. This seems a pretty performance-enhancing thing to do.

It is reminiscent of Richard Bird's paper on cyclic structures.

Peter




RE: doubly linked list

2000-04-28 Thread Chris Angus



> -Original Message-
> From: Peter Hancock [mailto:[EMAIL PROTECTED]]
> Sent: 28 April 2000 10:23
> To: [EMAIL PROTECTED]
> Cc: [EMAIL PROTECTED]
> Subject: Re: doubly linked list
> 
> 
> >>>>> "Jan" == Jan Kort <[EMAIL PROTECTED]> writes:
> 
> > Anyway, a doubly linked list could be defined like this:
> 
> That was very interesting.  It seems to generalise to put
> back-pointers and other context info in a variety of data
> structures. This seems a pretty performance-enhancing thing to do.
> 
> It is reminiscent of Richard Bird's paper on cyclic structures.
> 
> Peter
> 

I quite like the idea too but the thought of updating such a structure gives
me a headache.
Saying that ... this might encourage greater use of higher order fns rather
than
explicit recursion.








RE: doubly linked list

2000-04-28 Thread Chris Angus

Would it not be better to tag a start point then we can manipulate this
easier
and move it back to a singly linked list etc.

data Db a = Dd (Db a) a (Db a) 
  | DStart (Db a) a (Db a)

instance Show a => Show (Db a) where
 show xs = show (enumerate xs)

instance Eq a => Eq (Db a) where
 xs == ys = enumerate xs == enumerate ys

enumerate xs = enumerate' (rewind xs)
 
enumerate' (DStart _ v r) = v : enumerate'' r
enumerate' (Dd _ v r) = v : enumerate'' r
enumerate'' (DStart _ v r) = []
enumerate'' (Dd _ v r) = v : enumerate'' r

mapD f = dlink .(map f) .enumerate 

dlink ll = 
  let (hd,lst)=dble' ll lst hd
  dble [x] prev foll = 
let h = Dd prev x foll in (h,h)
  dble (x:xq) prev foll =
let h=Dd prev x nxt
(nxt,lst) = dble xq h foll
in (h,lst)
  dble' [x] prev foll = 
let h = DStart prev x foll in (h,h)
  dble' (x:xq) prev foll =
let h=DStart prev x nxt
(nxt,lst) = dble xq h foll
in (h,lst)
  in hd

left  (Dd a _ _) = a
left  (DStart a _ _) = a
right (Dd _ _ a) = a
right (DStart _ _ a) = a
val   (Dd _ x _) = x
val   (DStart _ x _) = x

rewind (Dd a _ _) = rewind a
rewind a = a

ffwd (Dd _ _ a) = ffwd a
ffwd a = a



> -Original Message-
> From: Jerzy Karczmarczuk [mailto:[EMAIL PROTECTED]]
> Sent: 28 April 2000 11:12
> Cc: [EMAIL PROTECTED]
> Subject: Re: doubly linked list
> 
> 
> > Jan Brosius wrote:
> 
> > I wonder if it is possible to simulate a doubly linked list in
> > Haskell.
> 
> ... and the number of answers was impressive...
> 
> Want some more?
> This is a short for *making* true double
> lists, and as an extra bonus it is circular. Slightly longer than
> the solution of Jan Kort, no empty lists.
> 
> A data record with three fields, the central is the value, other
> are pointers.
> 
> > data Db a = Dd (Db a) a (Db a) deriving Show
> -- (don't try to derive Eq...)
> 
> 
> dlink constructs a circular list out of a standard list. Cannot
> be empty. The internal fct. dble is the main iterator, which 
> constructs
> a dlist and links it at both ends to prev and foll.
> 
> > dlink ll = 
> >  let (hd,lst)=dble ll lst hd
> >  dble [x] prev foll = 
> >let h = Dd prev x foll in (h,h)
> >  dble (x:xq) prev foll =
> >let h=Dd prev x nxt
> >(nxt,lst) = dble xq h foll
> >in (h,lst)
> >  in hd
> 
> You might add some navigation utilities, e.g.
> 
> > left  (Dd a _ _) = a
> > right (Dd _ _ a) = a
> > val   (Dd _ x _) = x
> 
> etc. At least you don't need Monads nor Zippers. Keith Wansbrough
> proposes his article. I don't know it, when you find it please
> send me the references. But there are previous works, see the
> article published in Software 19(2), (1989) by Lloyd Allison,
> "Circular programs and self-referential structures".
> 
> 
> Jerzy Karczmarczuk
> Caen, France
> 
> PS. Oh, I see now that the KW article has been found...
> Well, I send you my solution anyway.
> 




Re: doubly linked list

2000-04-28 Thread Jerzy Karczmarczuk

Chris Angus:
> 
> Would it not be better to tag a start point then we can manipulate this
> easier
> and move it back to a singly linked list etc.
> 
> data Db a = Dd (Db a) a (Db a)
>   | DStart (Db a) a (Db a)
> 
> ...

Well, I am sufficiently old to confess that one of my favourite OO
languages, and the one where I found doubly-linked lists for the first
time was ...

Yes, Simula-67.

Actually *they did* that. A "node" had two sub-classes, the link and the
head, and the link chain was doubly attached to the head. This structure
has been havily used for the maintenance of the co-routine bedlam
exploited in simulation programs.

The idea of double lists was to permit a fast two-directional
navigation,
and the ease of insertion/deletion.

But in Haskell, where the beasts are not mutable:

... Actually, has anybody really used them for practical purposes?

Jerzy Karczmarczuk
Caen, France




Re: doubly linked list

2000-04-28 Thread Marc van Dongen

Jerzy Karczmarczuk ([EMAIL PROTECTED]) wrote:

: But in Haskell, where the beasts are not mutable:
: 
: ... Actually, has anybody really used them for practical purposes?

I have used doubly linked lists in Haskell about four
years ago to implement a queue from which objects could
be added at front/back and deleted anywhere.

A mutable array was used to see if objects were in the queue.
If they were then (Just Ix) to them would be returned
and if they weren't Nothing. The index could then be used
to find the possible previous and next elements in the queue
and change their representations. I cheated a bit because I used
the fact that the possible indices were know in advance so that
I could use an array to represent the member in the queue as
well. It worked well.

I've appended (what I think are the most important) code-fragments
at the end. I don't know if I would do it the same way again; this
was years ago.

Regards,


Marc van Dongen

> initQueue :: Ix i => (LinkedList s i v) -> [(i,v)] -> ST s (Maybe i,Maybe i)
> initQueue _ []
>   = return (Nothing,Nothing)
> initQueue marks ((i,v):ivs)
>   = writeArray marks i (Nothing,Nothing,Just v) >>
> a2q marks i i ivs

> addToQueue :: Ix i =>
>   (LinkedList s i v)
>  -> (Maybe i)
>  -> (Maybe i)
>  -> [(i,v)]
>  -> ST s (Maybe i,Maybe i)
> addToQueue marks fst lst  []
>   = return (fst,lst)
> addToQueue marks Nothing_  ijrs
>   = initQueue marks ijrs
> addToQueue marks (Just fst) (Just lst) ijrs
>   = a2q marks fst lst ijrs

> a2q :: Ix i =>
>   (LinkedList s i v)
>   -> i
>   -> i
>   -> [(i,v)]
>   -> ST s (Maybe i,Maybe i)
> a2q _ fst lst []
>   = return (Just fst,Just lst)
> a2q marks fst lst ((i,v):ivs)
>   = readArray marks i >>= \(_,_,mbv) ->
> case mbv of
>   Nothing -> readArray marks lst  >>= \(jpred,_,jv) ->
>  writeArray marks lst (jpred,Just i,jv)   >>
>  writeArray marks i (Just lst,Nothing,Just v) >>
>  a2q marks fst i ivs
>   _   -> a2q marks fst lst ivs

> delFromQueue :: Ix i =>
>   (LinkedList s i v)
>   -> (Maybe i)
>   -> (Maybe i)
>   -> [i]
>   -> ST s (Maybe i,Maybe i)
> delFromQueue _  jfstjlst[]
>   = return (jfst,jlst)
> delFromQueue marks  jfst@(Just fst) jlst@(Just lst) (i:is)
>   = readArray marks i  >>= 
>\(jpred,jsucc,_) ->
> writeArray marks i (Nothing,Nothing,Nothing)   >>
> case jpred of
>   Nothing  -> case jsucc of
> Nothing  -> return (Nothing,Nothing)
> (Just s) -> readArray marks s  >>= \(_,s',r') ->
> writeArray marks s (Nothing,s',r') >>
> delFromQueue marks jsucc jlst is
>   (Just p) -> case jsucc of
> Nothing  -> readArray marks p  >>= \(p',_,r') ->
> writeArray marks p (p',Nothing,r') >>
> delFromQueue marks jfst jpred is
> (Just s) -> readArray marks p  >>= \(p',_,r') ->
> writeArray marks p (p',jsucc,r')   >>
> readArray marks s  >>= \(_,s',r') ->
> writeArray marks s (jpred,s',r')   >>
> delFromQueue marks jfst jlst is




Re: doubly linked list

2000-04-28 Thread Peter Hancock

> "Jerzy" == Jerzy Karczmarczuk <[EMAIL PROTECTED]> writes:

> The idea of double lists was to permit a fast two-directional
> navigation,
> and the ease of insertion/deletion.

> But in Haskell, where the beasts are not mutable:

> ... Actually, has anybody really used them for practical purposes?

I think that if you want mutable double lists you would use a
representation with before/after lists.  Perhaps when you no longer
need mutable access (ie just "tape" operations) you can switch
to a representation with backthreading.

I suppose if there are parliaments of crows there may as well
be bedlams of coroutines.  
--
Peter





Fw: doubly linked list

2000-04-28 Thread Jan Brosius





 > Jerzy Karczmarczuk wrote:

 >
 > Yes, Simula-67.
 >
 > Actually *they did* that. A "node" had two sub-classes, the link and the
 > head, and the link chain was doubly attached to the head. This structure
 > has been havily used for the maintenance of the co-routine bedlam
 > exploited in simulation programs.
 >
 > The idea of double lists was to permit a fast two-directional
 > navigation,
 > and the ease of insertion/deletion.
 >
 > But in Haskell, where the beasts are not mutable:
 >
 > ... Actually, has anybody really used them for practical purposes?
 >
 > Jerzy Karczmarczuk
 > Caen, France
 >
 >

 Well I want to see the simulation of  a mutable  doubly linked list too.

 The author of  Lout writes in his documentation that after much searching
he
 was compelled

 to use doubly linked C lists.

 In Ocaml there was recently an online English version about using pointers
 in Ocaml

 (if people would like to do this) . I have got yesterday the solution of
 implementing

 doubly linked lists, it was rather short.


 I also wonder how one could simulate objects with mutable state in Haskell.

 Another question : is there any way to interrogate the typechecker from
 within a Haskell program?
 Could this be put on the wishlist?


 Friendly
Jan Brosius