Getting Unique Paths from list of tuple

一个人想着一个人 提交于 2019-12-21 20:54:44

问题


Given a tuple of lists, I need to find all unique path from that:

Example I/P: [(1,2),(2,3),(3,4),(9,11),(4,5),(5,6),(6,7),(3,9)]
O/P: [[(1,2),(2,3),(3,4),(4,5),(5,6),(6,7)],[(1,2),(2,3),(3,9),(9,11)]]

Two tuples can connect if the second element of the tuple matches with the first element of the other tuple i.e: One tuple is (_,a) and other tuple is like (a,_).

What is the most efficient implementation for this ? I need to find the best data structure suited for it. Any suggestions ? The number of tuples in which I will execute the algorithm will be like more than 400,000.


回答1:


{-# LANGUAGE NoMonomorphismRestriction #-}
import Data.List (permutations, nub)

path :: Eq a => [(a, a)] -> [(a, a)]
path [] = []
path [x] = [x]
path (u@(_, a):v@(b, _):xs) = if a == b then u:path (v:xs) else [u]

allPaths = nub . map path . permutations

(you can optimize chain generation but I think this problem has exponential time complexity)

EDITED

In general, you must to define more preciselly what paths you want to return.

Ignoring cycle invariant ([(1,2),(2,3),(3,1)] == [(2,3),(3,1),(1,3)]) you can generate all paths (without using permutations)

{-# LANGUAGE NoMonomorphismRestriction #-}
import Data.List (permutations, nub, sortBy, isInfixOf)

data Tree a = Node a [Tree a] deriving Show

treeFromList :: Eq a => a -> [(a, a)] -> Tree a
treeFromList a [] = Node a []
treeFromList a xs = Node a $ map subTree $ filter ((a==).fst) xs
  where subTree v@(_, b) = treeFromList b $ filter (v/=) xs

treesFromList :: Eq a => [(a, a)] -> [Tree a]
treesFromList xs = map (flip treeFromList xs) $ nub $ map fst xs ++ map snd xs

treeToList :: Tree a -> [[a]]
treeToList (Node a []) = [[a]]
treeToList (Node a xs) = [a:ws | ws <- concatMap treeToList xs]

treesToList :: [Tree a] -> [[a]]
treesToList = concatMap treeToList

uniqTrees :: Eq a => [[a]] -> [[a]]
uniqTrees = f . reverse . sortBy ((.length).compare.length)
  where f [] = []
        f (x:xs) = x: filter (not.flip isInfixOf x) (f xs)

allPaths = uniqTrees . treesToList . treesFromList

then

*Main> allPaths [(1, 2), (1, 3), (2, 3), (2, 4), (3, 4), (4, 1)]
[[2,4,1,2,3,4],[2,3,4,1,2,4],[1,3,4,1,2,4],[1,3,4,1,2,3],[1,2,4,1,3,4],[1,2,3,4,1,3]]

uniqTrees has poor efficiency and, in general, you can do many optimizations.

If you want to avoid cycle invariant, you can normalize a cycle selecting minimum base10 representation, in previous example ([(1,2),(2,3),(3,1)] == [(2,3),(3,1),(1,3)]) 1231 < 2313 then

normalize [(2,3),(3,1),(1,3)] == [(1,2),(2,3),(3,1)]

you can normalize a path rotating it n-times and taking "head . sortBy toBase10 . rotations".




回答2:


I think your problem fits on the NP category since:

A Hamiltonian path, also called a Hamilton path, is a path between two vertices of a graph that visits each vertex exactly once.

In general, the problem of finding a Hamiltonian path is NP-complete (Garey and Johnson 1983, pp. 199-200), so the only known way to determine whether a given general graph has a Hamiltonian path is to undertake an exhaustive search (source)

You problem is even "harder" since you don't know before hand what will be the end node.

In terms of data structure you can try to simulate the hash table structure in Haskell, since this data type is commonly use in graph and you problem can be turn into a graph.



来源:https://stackoverflow.com/questions/14706041/getting-unique-paths-from-list-of-tuple

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!