chimera-0.2.0.0: Lazy, infinite streams with O(1) indexing.

Copyright(c) 2017 Andrew Lelechenko
LicenseMIT
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Chimera.ContinuousMapping

Description

Helpers for continuous mappings, useful to memoize predicates on Int (instead of Word only), and predicates over two, three and more arguments.

Example

An infinite plain board of live and dead cells (common for cellular automatons, e. g., Conway's Game of Life) can be represented as a predicate board :: Int -> Int -> Bool. Assume that we want to convert it to memoized form. We cannot do it directly, because tabulate accepts predicates from Word to Bool only.

The first step is to define:

board'' :: Int -> Int -> Bool
board'' x y = board' (intToWord x) (intToWord y)

board' :: Word -> Word -> Bool
board' x y = board (wordToInt x) (wordToInt y)

This is better, but board' is a predicate over two arguments, and we need it to be a predicate over one. Conversion to Z-curve and back does the trick:

board'' :: Int -> Int -> Bool
board'' x y = board1 $ toZCurve (intToWord x) (intToWord y)

board' :: Word -> Bool
board' z = let (x, y) = fromZCurve z in
           board (wordToInt x) (wordToInt y)

Now we are ready to insert memoizing layer:

board'' :: Int -> Int -> Bool
board'' x y = index board' $ toZCurve (intToWord x) (intToWord y)

board' :: Chimera
board' = tabulate $
  \z -> let (x, y) = fromZCurve z in
        board (wordToInt x) (wordToInt y)
Synopsis

Documentation

intToWord :: Int -> Word Source #

Total map, which satisfies inequality abs (intToWord x - intToWord y) ≤ 2 abs(x - y).

Note that this is not the case for fromIntegral :: Int -> Word, 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)]