[Haskell-cafe] Updating doubly linked lists
Niklas Broberg
niklas.broberg at gmail.com
Sat Jan 3 09:43:46 EST 2009
> Is it possible to change a particular node of the
> doubly linked list? That is to say, that would like
> to have a function:
> update :: DList a -> a -> DList a
> where
> update node newValue
> returns a list where only the value at the node
> which is passed in is set to the new Value and
> all other values are the same.
What you need is for the nodes to keep track of the length of the
list. Here's a different solution from that oleg posted, to me it's
slightly more intuitive, since the updates work directly on the dlists
instead of via (elegant) proxy functions.
----------------------------------------------------------------------
module DList where
data DList a
= DNode Int (DList a) a (DList a)
| Empty
mkDList :: [a] -> DList a
mkDList [] = Empty
mkDList xs =
let len = length xs
this = DNode len farLeft (head xs) nearRight
(nearRight,farLeft) = mkRestDList len (tail xs) this this
in this
mkRestDList :: Int -> [a] -> DList a -> DList a -> (DList a, DList a)
mkRestDList _ [] _ farRight =
(farRight, farRight) -- will only happen if the initial list is singleton
mkRestDList len [x] nearLeft farRight =
let this = DNode len nearLeft x farRight
in (this, this)
mkRestDList len (x:xs) nearLeft farRight =
let this = DNode len nearLeft x nearRight
(nearRight,farLeft) = mkRestDList len xs this farRight
in (this,farLeft)
takeD :: Int -> DList a -> [a]
takeD 0 _ = []
takeD _ Empty = []
takeD n (DNode _ _ x r) = x : takeD (n-1) r
leftD, rightD :: DList a -> DList a
leftD Empty = Empty
leftD (DNode _ l _ _) = l
rightD Empty = Empty
rightD (DNode _ _ _ r) = r
updateD :: a -> DList a -> DList a
updateD _ Empty = Empty
updateD x (DNode len _ _ r) =
let this = DNode len farLeft x nearRight
(nearRight,farLeft) = updateRestD (len-1) r this this
in this
updateRestD :: Int -> DList a -> DList a -> DList a -> (DList a, DList a)
updateRestD 0 _ _ farRight =
(farRight, farRight) -- will only happen if the initial list is singleton
updateRestD 1 (DNode len _ x _) nearLeft farRight =
let this = DNode len nearLeft x farRight in (this, this)
updateRestD n (DNode len _ x r) nearLeft farRight =
let this = DNode len nearLeft x nearRight
(nearRight,farLeft) = updateRestD (n-1) r this farRight
in (this,farLeft)
updateRestD _ Empty _ _ = undefined -- can't happen
-----------------------------------------------------
*DList> let dl = mkDList [1..5]
*DList> takeD 11 dl
[1,2,3,4,5,1,2,3,4,5,1]
*DList> let dl' = updateD (-1) dl
*DList> takeD 11 dl'
[-1,2,3,4,5,-1,2,3,4,5,-1]
Cheers,
/Niklas
More information about the Haskell-Cafe
mailing list