module Data.Graph.Inductive.Internal.RootPath (
RTree,LRTree,
getPath,getLPath,
getDistance,
getLPathNodes
) where
import Data.Graph.Inductive.Graph
type LRTree a = [LPath a]
type RTree = [Path]
first :: ([a] -> Bool) -> [[a]] -> [a]
first :: forall a. ([a] -> Bool) -> [[a]] -> [a]
first [a] -> Bool
p [[a]]
xss = case forall a. (a -> Bool) -> [a] -> [a]
filter [a] -> Bool
p [[a]]
xss of
[] -> []
[a]
x:[[a]]
_ -> [a]
x
findP :: Node -> LRTree a -> [LNode a]
findP :: forall a. Node -> LRTree a -> [LNode a]
findP Node
_ [] = []
findP Node
v (LP []:[LPath a]
ps) = forall a. Node -> LRTree a -> [LNode a]
findP Node
v [LPath a]
ps
findP Node
v (LP (p :: [LNode a]
p@((Node
w,a
_):[LNode a]
_)):[LPath a]
ps) | Node
vforall a. Eq a => a -> a -> Bool
==Node
w = [LNode a]
p
| Bool
otherwise = forall a. Node -> LRTree a -> [LNode a]
findP Node
v [LPath a]
ps
getPath :: Node -> RTree -> Path
getPath :: Node -> RTree -> Path
getPath Node
v = forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ([a] -> Bool) -> [[a]] -> [a]
first (\(Node
w:Path
_)->Node
wforall a. Eq a => a -> a -> Bool
==Node
v)
getLPath :: Node -> LRTree a -> LPath a
getLPath :: forall a. Node -> LRTree a -> LPath a
getLPath Node
v = forall a. [LNode a] -> LPath a
LP forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Node -> LRTree a -> [LNode a]
findP Node
v
getDistance :: Node -> LRTree a -> Maybe a
getDistance :: forall a. Node -> LRTree a -> Maybe a
getDistance Node
v LRTree a
t = case forall a. Node -> LRTree a -> [LNode a]
findP Node
v LRTree a
t of
[] -> forall a. Maybe a
Nothing
(Node
_,a
d):[LNode a]
_ -> forall a. a -> Maybe a
Just a
d
getLPathNodes :: Node -> LRTree a -> Path
getLPathNodes :: forall a. Node -> LRTree a -> Path
getLPathNodes Node
v = (\(LP [LNode a]
p)->forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [LNode a]
p) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Node -> LRTree a -> LPath a
getLPath Node
v