[Haskell-cafe] Re: Doubly-linked zipper list w/ insert
implementation
apfelmus
apfelmus at quantentunnel.de
Sat Nov 10 15:24:45 EST 2007
Justin Bailey wrote:
> The other day I decided to implement a ring buffer with a current
> element (i.e. a doubly-linked zipper list).
>
> [...]
>
> p.s. The original motivation for writing this was to model cellular
> automata. The CA world is "circular", so that got me thinking about a
> structure that made connecting the ends easy to do.
Note that depending on your concrete setting, you may not need a fancy
ring structure for cellular automata. And with simple automata like
c'_i = c_(i-1) `xor` c_i `xor` c_(i+1)
it may even be easier to generate fresh rings for each step in the
automaton:
data Context a = Context [a] a [a]
-- rotate left
rotL (Context ls x (r:rs)) = Context (x:ls) r rs
-- description of a cellular automaton
type Rule a = Context a -> a
example :: Rule Bool
example (Context (cm:_) c (cp:_)) = cm `xor` c `xor` cp
-- run a cellular automaton on an initial band of cells
-- which is considered to be cyclic, i.e. a "cylinder"
automate :: Rule a -> [a] -> [[a]]
automate f xs = iterate (take n . map f . mkContexts) xs
where
-- length of the cell band
n = length xs
mkContexts (x:xs) = iterate rotL $
Context (cycle $ reverse xs) (head xs) (tail $ cycle xs)
Here, mkContexts xs initializes a new infinite cyclic "ring" for xs
and rotates it left ad infinitum.
Regards,
apfelmus
More information about the Haskell-Cafe
mailing list