At 18:20 2000-03-31 -0500, Wayne Young wrote:
>I appreciate any insight anyone has to offer on this code.
I tinkered a bit, and have a modicum of information to show for it. Here's
a translation to Haskell, with what seems to be the right implementation of
xor_iscan. I don't know what sequences you're supposed to feed into
generateDeBruign, but it seems to be fairly easy to find some that work.
Below, db5 provides some examples that work, and some that don't.
import List
import Maybe
xor_iscan :: Integral t => [t] -> [t]
xor_iscan = scanl1 xor
where
xor 0 0 = 0
xor 1 1 = 0
xor _ _ = 1
nextDeBruijn :: ([Int], Int, Int) -> [Int]
nextDeBruijn (w, i, k) =
part1 ++ part2 ++ part3 ++ part4 -- concatenate the list for output
where
c = xor_iscan w -- apply (inclusive) prefix scan
cbar = do { a <- c; return (1 - a)} -- compute the bit-complement of
the sequence
part1 = take (i - k) c -- take the first i - k bits from C
part2 = drop (i - 1 + k) cbar -- drop the first i - 1 + k bits from Cbar
part3 = take (i - 1 + k) cbar -- take the first i - 1 + k bits from Cbar
part4 = drop (i - k) c -- drop the first i - k bits from C in
generateDeBruijn :: (Int, [Int]) -> [Int]
generateDeBruijn (n, x) =
if (n == 2) then [1,1,0,0]
else if (n == 3) then
if (x !! 0 == 0) then [1,0,1,1,1,0,0,0]
else [1,1,1,0,1,0,0,0]
else nextDeBruijn (generateDeBruijn(n-1,x), 2 ^ (n-2) + (-1) ^ (x !!
(n-4)), x !! (n-3))
db2 = generateDeBruijn (2, [])
db3 = do a <- [0..1]
return (generateDeBruijn (3, [a]))
db4 = do a <- [0..1]
b <- [0..1]
return (generateDeBruijn (4, [a,b]))
db5 = do a <- [0..1]
b <- [0..1]
c <- [0..3]
return (generateDeBruijn (5, [a,b,c]))
-- test whether a list is a deBruign sequence, not efficient
check :: [Int] -> Bool
check l = ((length $ nub $ sort $ lists) == len)
where
len = length l
logLen = logi len :: Int
c :: [Int]
c = cycle l
lists :: [[Int]]
lists = map makeList [0..len - 1]
makeList :: Int -> [Int]
makeList n = take logLen $ drop n c
logi :: Int -> Int
logi i = (fromJust $ elemIndex 0 (iterate (`div` 2) i)) - 1
--
Scott Turner
[EMAIL PROTECTED] http://www.ma.ultranet.com/~pkturner