| Copyright | (c) 2017 Andrew Lelechenko |
|---|---|
| License | MIT |
| Maintainer | Andrew Lelechenko <andrew.lelechenko@gmail.com> |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Chimera.ContinuousMapping
Description
Helpers for continuous mappings, useful to memoize
functions on Int (instead of Word only) and
functions over two and three arguments.
Example 1
Imagine writing a program to simulate
Rule 90.
This is a cellular automaton,
which consists of an infinite one-dimensional line of cells,
each being either dead (False) or alive (True).
If two neighbours of a cell are equal,
it becomes dead on the next step, otherwise alive.
Usually cellular automata are modelled by a finite vector. This is a bit suboptimal, because cellular automata may grow in different directions over time, but with a finite vector one has to define a bounding segment well beforehand. Moreover, what if we are interested to explore an evolution of an essentially infinite initial configuration?
It would be natural to encode an initial configuration
as a function Int -> Bool, which takes a coordinate
and returns the status of the corresponding cell. Define
a function, which translates the automaton to the next step:
step :: (Int -> Bool) -> (Int -> Bool) step current = \n -> current (n - 1) /= current (n + 1)
Unfortunately, iterating step would be extremely slow
because of branching recursion. One
could suggest to introduce a caching layer:
step :: (Int -> Bool) -> (Int -> Bool)
step current = \n -> current' (n - 1) /= current' (n + 1)
where
current' = memoize (current . fromIntegral) . fromIntegralUnfortunately, it would not work well,
because fromIntegral :: Int -> Word
maps -1 to maxBound and it would take ages to memoize
everything up to maxBound.
But continuous mappings intToWord and wordToInt avoid this issue:
step :: (Int -> Bool) -> (Int -> Bool)
step current = \n -> current' (n - 1) /= current' (n + 1)
where
current' = memoize (current . wordToInt) . intToWordExample 2
What about another famous cellular automaton:
Conway's Game of Life?
It is two-dimensional, so its state can be represented as
a function Int -> Int -> Bool. Following the approach above,
we would like to memoize such functions.
Namely, cast the state to Word -> Bool, ready for memoization:
cast :: (Int -> Int -> Bool) -> (Word -> Bool) cast f = \n -> let (x, y) = fromZCurve n in f (word2int x) (word2int y)
and then back:
uncast :: (Word -> Bool) -> (Int -> Int -> Bool) uncast g = \x y -> g (toZCurve (int2word x) (int2word y))
Documentation
intToWord :: Int -> Word Source #
Total map, which satisfies
abs (intToWord x - intToWord y) <= 2 * abs (x - y)
Note that usual fromIntegral :: Int -> Word does not
satisfy this inequality,
because it has a discontinuity between −1 and 0.
>>>map intToWord [-5..5][9,7,5,3,1,0,2,4,6,8,10]
wordToInt :: Word -> Int Source #
Inverse for intToWord.
>>>map wordToInt [0..10][0,-1,1,-2,2,-3,3,-4,4,-5,5]
toZCurve :: Word -> Word -> Word Source #
Total map from plain to line, continuous almost everywhere. See Z-order curve.
Only lower halfs of bits of arguments are used (32 bits on 64-bit architecture).
>>>[ toZCurve x y | x <- [0..3], y <- [0..3] ][0,2,8,10,1,3,9,11,4,6,12,14,5,7,13,15]
fromZCurve :: Word -> (Word, Word) Source #
Inverse for toZCurve.
See Z-order curve.
>>>map fromZCurve [0..15][(0,0),(1,0),(0,1),(1,1),(2,0),(3,0),(2,1),(3,1),(0,2),(1,2),(0,3),(1,3),(2,2),(3,2),(2,3),(3,3)]
toZCurve3 :: Word -> Word -> Word -> Word Source #
Total map from space to line, continuous almost everywhere. See Z-order curve.
Only lower thirds of bits of arguments are used (21 bits on 64-bit architecture).
>>>[ toZCurve3 x y z | x <- [0..3], y <- [0..3], z <- [0..3] ][0,4,32,36,2,6,34,38,16,20,48,52,18,22,50,54,1,5,33,37,3,7,35,39,17,21,49,53,19,23,51,55, 8,12,40,44,10,14,42,46,24,28,56,60,26,30,58,62,9,13,41,45,11,15,43,47,25,29,57,61,27,31,59,63]
fromZCurve3 :: Word -> (Word, Word, Word) Source #
Inverse for toZCurve3.
See Z-order curve.
>>>map fromZCurve3 [0..63][(0,0,0),(1,0,0),(0,1,0),(1,1,0),(0,0,1),(1,0,1),(0,1,1),(1,1,1),(2,0,0),(3,0,0),(2,1,0),(3,1,0),(2,0,1),(3,0,1),(2,1,1),(3,1,1), (0,2,0),(1,2,0),(0,3,0),(1,3,0),(0,2,1),(1,2,1),(0,3,1),(1,3,1),(2,2,0),(3,2,0),(2,3,0),(3,3,0),(2,2,1),(3,2,1),(2,3,1),(3,3,1), (0,0,2),(1,0,2),(0,1,2),(1,1,2),(0,0,3),(1,0,3),(0,1,3),(1,1,3),(2,0,2),(3,0,2),(2,1,2),(3,1,2),(2,0,3),(3,0,3),(2,1,3),(3,1,3), (0,2,2),(1,2,2),(0,3,2),(1,3,2),(0,2,3),(1,2,3),(0,3,3),(1,3,3),(2,2,2),(3,2,2),(2,3,2),(3,3,2),(2,2,3),(3,2,3),(2,3,3),(3,3,3)]