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.
> 

Reply via email to