99 questions/Solutions/82

From HaskellWiki
< 99 questions‎ | Solutions
Revision as of 06:29, 31 July 2021 by Chestersimpson (talk | contribs) (list as monad)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search

Brute-force search from the source, using list comprehension:

 import Data.List (partition)
 cycle' :: Int -> [(Int, Int)] -> [ [Int] ]
 cycle' n g = search [[n]] []
   where search [] result = result
         search cur result = search (go active) (arrive ++ result)
           where split = partition end cur
                 end s = (last s == n) && (length s /= 1)
                 active = snd split
                 arrive = fst split
                 go ls = [ x ++ [snd y] | x <- ls, y <- g, last x == fst y, not (snd y `elem` tail x)]

another approach using list as monad

cycles :: (Eq a) => a -> [Arc a] -> [[a]]
cycles _ [] = []
cycles start arcs = 
    map (map fst) $ aux start []
        where 
            aux current pathSoFar = 
                let nextEdges = filter ((== current) . fst) arcs 
                    notCyclic = not . (\(_,t) -> (elem t $ map snd pathSoFar)) 
                    noCycles  = filter notCyclic nextEdges
                in  noCycles >>= \(f,t) -> do 
                                              if (t == start) then return $ pathSoFar ++ (f,t):[(t,t)]
                                                              else aux t (pathSoFar ++ [(f,t)])