module Data.List.NP where import Data.Array import Data.List (tails) interleave :: [a] -> [a] -> [a] interleave [] ys = ys interleave (x:xs) ys = x : interleave ys xs -- | Given a `choose' function and bound indices, it returns the list of indices -- following a dichotomic search. -- The `choose' function, picks an index between to other indices or return -- Nothing if this is not possible, like when indices are too close each other. dichoIndices :: (ix -> ix -> Maybe ix) -> (ix, ix) -> [ix] dichoIndices choose (begin, end) = begin : end : go begin end where go b e = case choose b e of Nothing -> [] Just m -> m : interleave (go b m) (go m e) -- | Order the given list by distance with previous elements, starting -- from the higher distance. -- It starts with the first element, then the last one, then the middle -- one... orderByDensity :: [a] -> [a] orderByDensity xs = map (arr!) (dichoIndices choose bnds) where arr = listArray bnds xs bnds = (0, length xs - 1) choose x y | y - x <= 1 = Nothing | otherwise = Just (x + (y - x) `div` 2) zipTailWith :: (a -> a -> b) -> [a] -> [b] zipTailWith _ [] = [] zipTailWith f (x0 : xs0) = go x0 xs0 where go _ [] = [] go x (y:ys) = f x y : go y ys orderByDensity_spec :: Int -> Bool orderByDensity_spec n = go (orderByDensity input) where input = [0..n] :: [Int] -- thanks to parametricity dist x y = abs (y - x) distL [] = error "orderByDensity_spec: impossible" distL (x:xs) = minimum (map (dist x) xs) go = and . zipTailWith (<=) . map distL . init . init . tails . reverse