FuGeo07 Funktionale Modellierung f ur Geoinformationssysteme WS 2010/11 FGL: Funktionale Bibliothek zur Behandlung sehr allgemeiner Graphen (Martin Erwig) http://web.engr.oregonstate.edu/ erwig/fgl/ • Knoten und Kanten markiert Die Graphenbibliothek FGL • Mehrfahkanten zwishen Knoten (durh Markierung untershieden) • unmarkierter Fall: Markierungen vom trivialen Typ () Beispiel B. M oller • Automatendiagramme • Verkehrsnetze B. M oller/S. Timpf 1 { 1 { FuGoe WS 10/11 2 B. M oller/S. Timpf { 2 { FuGoe WS 10/11 Induktiver Aufbau von Graphen type Node = Int type Graph a b = -- statt Int könnte auch ein -- abstrakter Typ (in Typklasse eingeführt) der -- beliebiger anderer Typ von -- Graphen mit Knoten-/Kantenmarkierungen vom Typ a/b -- "Knotennamen" stehen type LNode a = (Node,a) type UGraph -- a Typ der Knotenmarkierungen type UNode = LNode () type Path -- unmarkierte Knoten = (Node,Node) type LEdge b = (Node,Node,b) type LPath a = [Node] = [LNode a] -- Pfad mit Knotenmarkierungen -- b Typ der Kantenmarkierungen = Graph () () -- Pfad als reine Knotenfolge type Edge type UEdge = -- unmarkierter Graph type UPath = [UNode] LEdge () -- unmarkierte Kanten B. M oller/S. Timpf { 3 { FuGoe WS 10/11 B. M oller/S. Timpf { 4 { FuGoe WS 10/11 Grundidee fur Graphenaufbau: • F uge nah und nah Knoten ein, jeweils mit ihren Verbindungen Ein Knoten x mit seiner Eingangs- und Ausgangsadjazenz bildet einen Kontext: zu bereits bestehenden Knoten. GFED @ABC @ABC GFED y1 H z HbH1 c1 vv:: 1 v H $$ v .. .. 89:; ?>=< x . u:: III . u I uu cn $$ @ABC GFED @ABC GFED yk bk zn • Ausgangspunkt ist jeweils der leere Graph empty :: Graph a b emptyU :: UGraph • Verbindungen werden dargestellt durh Adjazenzlisten: type Adj b = [(b,Node)] B. M oller/S. Timpf type Context a b { 5 { FuGoe WS 10/11 Bevor wir Operationen zum Einfugen von Kontexten, also von neuen Knoten, in Graphen angeben, besprehen wir als Umkehrung eine Zerlegungsoperation. B. M oller/S. Timpf = (Adj b,Node,a,Adj b) { 6 { FuGoe WS 10/11 Umgekehrt kann man einen passenden Kontext in einen Graphen einfugen: embed :: Context a b -> Graph a b -> Graph a b Fur einen Knoten x in einem Graphen G kann man G zerlegen in den Kontext von x, bestehend aus seinen beiden Adjazenzlisten, seiner Nummer und seiner Markierung, sowie den Restgraphen G ′ , der durh Streihen von x und seiner ein- und ausgehenden Kanten entsteht. B. M oller/S. Timpf { 7 { FuGoe WS 10/11 embedU :: UContext -> UGraph -> UGraph Dafur wird auh ein Inxoperator eingefuhrt: infixr & c & g = embed c g B. M oller/S. Timpf { 8 { FuGoe WS 10/11 Fur die Graphen ist eine show-Funktion deniert, die der Reihe die Knoten mit ihren Ausgangsadjazenzen ausgibt: Beispiel uArc n = ((),n) -- "Halbkante" mit Knoten n und leerer Markierung GraphData> a 1:’a’->[] a = ([],1,’a’,[]) & empty -- Einzelknoten; GraphData> loop -- streng genommen ist hier für eine der leeren Adjazenzen 1:’a’->[((),1)] -- der Typ [] :: Adj () explizit anzugeben loop = ([],1,’a’,[uArc 1]) & empty GraphData> e -- Einzelknoten mit Schlinge e = 1:’a’->[((),2)] ([uArc 1],2,’b’,[]) & a 2:’b’->[] -- Kante a --> b ab = ([uArc 1],2,’b’,[uArc 1]) & a GraphData> ab -- Zyklus aus zwei Knoten a <--> b 1:’a’->[((),2)] 2 B. M oller/S. Timpf FuGoe WS 10/11 { 9 { 2:’b’->[((),1)] B. M oller/S. Timpf { 10 { FuGoe WS 10/11 Ein Graph kann in der Regel auf vershiedene Weisen aufgebaut werden: g3 = ([("left",2),("up",3)]),1,’a’,[("right",2)]) & ([],2,’b’,[("down",3)]) & ([],3,’c’,[]) & • endlihe Abbildungen von Knoten auf Restkontexte type Context’ a b = (Adj b,a,Adj b) empty g3’ = Eine moglihe Implementierung: • tatsahlihe Implementierung etwas komplexer, um die EÆzienz ([("down",2)]),3,’c’,[(("up",1)]) zu verbessern & ([("right",1)],2,’b’,[("left",1)]) & ([],l,’a’,[]) & empty B. M oller/S. Timpf { 11 { FuGoe WS 10/11 B. M oller/S. Timpf { 12 { FuGoe WS 10/11 Zum bequemen Arbeiten fuhrt man eine Reihe von Hilfsfunktionen auf embed zuruk: insNode :: LNode a -> Graph a b -> Graph a b ucycle :: Int -> UGraph insNodes :: [LNode al -> Graph a b -> Graph a b insEdge Beispiel Konstruktion von Zyklen und sternformigen Graphen ucycle n = mkUGraph vs (map (\v->(v,v ‘mod‘ n+1)) vs) :: LEdge b -> Graph a b -> Graph a b where vs = [1..n] insEdges :: [LEdge b] -> Graph a b -> Graph a b newNodes :: Int -> Graph a b -> [Node] star :: Int -> UGraph -- Liste einiger im Graphen noch nicht enthaltenen Knoten mkGraph star n = mkUGraph [1..n] (map (\v->(1,v)) [2..n]) 2 :: [LNode a] -> [LEdge b] -> Graph a b mkUGraph :: [Node] -> [Edge] -> UGraph B. M oller/S. Timpf 2 { 13 { FuGoe WS 10/11 Die folgenden typishen Funktionen konnen induktiv u ber den Graphenaufbau deniert werden. Zunahst Informationen uber gesamte Graphen: isEmpty :: Graph a b -> Bool noNodes :: Graph a b -> Int -- Knotenzahl nodes :: Graph a b -> [Node] -- Knotenmenge als Liste labNodes :: Graph a b -> [LNode a] -- Liste der markierten Knoten edges :: Graph a b -> [Edge] -- Kantenmenge als Liste labEdges :: Graph a b -> [LEdge b] -- Liste der markierten Kanten { 15 { FuGoe WS 10/11 { 14 { Informationen u ber einzelne Knoten: Ableseoperationen B. M oller/S. Timpf B. M oller/S. Timpf FuGoe WS 10/11 suc :: Graph a b -> Node -- Nachfolger pre :: Graph a b -> Node -- Vorgänger neighbors :: Graph a b -> Node -- Vorgänger und Nachfolger out :: Graph a b -> Node -- ausgehende Kanten inn :: Graph a b -> Node -- einlaufende Kanten outdeg :: Graph a b -> Node -- Ausgangsgrad indeg :: Graph a b -> Node -- Eingangsgrad deg :: Graph a b -> Node -- Grad B. M oller/S. Timpf { 16 { -> [Node] -> [Node] -> [Node] -> [LEdge b] -> [LEdge b] -> Int -> Int -> Int FuGoe WS 10/11 Diese Funktionen sind auh fur Kontexte wihtig: suc’ :: 3 pre’ :: Context a b -> [Node] neighbors’ :: Context a b -> [Node] out’ :: Context a b -> [LEdge b] inn’ :: Context a b -> [LEdge b] outdeg’ :: Context a b -> Int indeg’ :: Context a b -> Int deg’ :: Context a b -> Int node’ :: Context a b -> Node Bei den Ableseoperationen war keine Fehlerbehandlung notig. Bei der Zerlegung ist das anders, weil der Fall abgefangen werden muss, dass der Zerlegungsknoten gar niht im Graphen vorkommt. Fur solhe Falle gibt es in data Maybe a :: = Haskell den Standardtyp Maybe: Just a | Nothing Dabei stellt der Konstruktor Just die Variante der ordentlihen\ " Ergebniswerte vom Typ a dar, wahrend Nothing ein Ersatzwert im Fehlerfall ist. -- zentraler Knoten des Kontexts lab’ Graphzerlegung Context a b -> [Node] Context a b -> a -- seine Markierung labNode’ :: Damit kann man auf eine ehte Ausnahmebehandlung verzihten, die in Haskell zwar moglih aber etwas umstandlih ist. Context a b -> LNode a -- zentraler Knoten mit Markierung B. M oller/S. Timpf { 17 { FuGoe WS 10/11 Fur unsere Anwendung denieren wir folgende Typen: type MContext a b = B. M oller/S. Timpf { 18 { FuGoe WS 10/11 GraphData> match 1 a (Just ([],1,’a’,[]),) Maybe (Context a b) -- Restgraph leer type Decomp a b type GDecomp a b = = (MContext a b,Graph a b) (Context a b,Graph a b) GraphData> match 1 loop (Just ([],1,’a’,[((),1)]),) type UContext type UDecomp = = -- Restgraph leer ([Node],Node,[Node]) (Maybe UContext,UGraph) -- Schlingenpfeil nur in einer Adjazenz! Die Zerlegungsfunktionen GraphData> match 1 ab (Just ([((),2)],1,’a’,[((),2)]), match :: Node -> Graph a b -> Decomp a b matchU :: Node -> UGraph -> UDecomp 2:’b’->[]) liefern dann den Ersatzkontext Nothing, wenn der betrahtete Knoten niht im Graphen liegt, wahrend der Graph unverandert als Restgraph zurukgeliefert wird. B. M oller/S. Timpf { 19 { FuGoe WS 10/11 GraphData> match 1 e (Just ([],1,’a’,[((),2)]), 2:’b’->[]) B. M oller/S. Timpf { 20 { FuGoe WS 10/11 Weitere Operationen konnen darauf zurukgefuhrt werden: matchP :: Node -> Graph a b -> Decomp a b -- wie match, fügt aber Schlingenkanten in die -- Vorgängerliste ein GraphData> match 2 a (Nothing, 1:’a’->[]) matchAny :: Graph a b -> GDecomp a b -- unbestimmte Zerlegung; -- Fehler bei leerem Graphen GraphData> match 1 g3 (Just ([("left",2), ("up",3)] ,1,’a’ , [("right",2)]), 2: ’b’->[("down",3)] (Graph a b -> Node -> Bool) -> Graph a b -> GDecomp a b -- Zerlegung an unbestimmtem Knoten, -- der ein Prädikat erfüllt 3:’c’->[]) Fur match gilt folgende Rekombinationseigenshaft: match v g = (Just c,g’) => matchSome :: matchThe :: c & g’ = g (Graph a b -> Node -> Bool) -> Graph a -> GDecomp a b -- dito; aber es darf nur einen erfüllenden Knoten geben B. M oller/S. Timpf { 21 { FuGoe WS 10/11 B. M oller/S. Timpf 4 context :: Node -> Graph a b -> Context a b contextP :: Node -> Graph a b -> Context a b :: Node -> Graph a b -> Graph a b delNodes :: [Node] -> Graph a b -> Graph a b delEdge :: Edge -> Graph a b -> Graph a b delEdges :: [Edge] -> Graph a b -> Graph a b FuGoe WS 10/11 Allgemeine Graphenoperationen Zunahst besprehen wir Funktionen zum systematishen Durhlaufen von Graphen. -- Zerlegungen ohne Restgraphen delNode { 22 { Die erste ist eine Analogon zur map-Funktion auf Listen: gmap :: (Context a b -> Context c d) -> Graph a b -> Graph c d gmap f g -- Löschen von Knoten bzw. Kanten = if isEmpty g then else empty f c & gmap f g’ where (c,g’) = matchAny g B. M oller/S. Timpf { 23 { FuGoe WS 10/11 B. M oller/S. Timpf { 24 { FuGoe WS 10/11 Weitere hilfreihe Funktionen: Beispiel Jeder Knoten des Graphen soll als Markierung die Char-Darstellung seiner Nummer erhalten: grev :: Graph a b -> Graph a b -- Umkehren aller Kanten gmap (\(p,v,_,s) -> (p,v,chr(96+v),s)) undir 2 :: Graph a b -> Graph a b -- reichere den Graphen um fehlende symmetrisierte Kanten -- zur Darstellung des zugehörigen ungerichteten Graphen an Spezialfalle von gmap sind Funktionen zum systematishen Berbeiten aller Knoten- bzw. Kantenmarkierungen: nmap :: (a -> c) -> Graph a b -> Graph c b emap :: (b -> c) -> Graph a b -> Graph a c B. M oller/S. Timpf 5 { 25 { unlab :: Graph a b -> UGraph -- erzeuge den unterliegenden unmarkierten Graphen gsel :: (Context a b -> Bool) -> Graph a b -> [Context a b] -- Liste aller Kontexte, die ein Prädikat erfüllen FuGoe WS 10/11 B. M oller/S. Timpf { 26 { FuGoe WS 10/11 Kürzeste Wege Grundlage: mishbare Halden • wesentlih exibler als gewohnlihe binare Halden • beliebig verzweigte Baume • aber Haldenbedingung erf ullt: an der Wurzel das Minimum der Knotenwerte • Vereinigung zweier Halden: hange die mit dem groeren Wurzelwerte als zusatzlihes Kind unter die Wurzel mit dem kleineren Wert • daraus lasst sih induktiv eine allgemeine Vereinigungsoperation fur endlih viele Halden denieren • Extraktion des Minimums: Wurzel abshneiden und aller Kinder vereinigen B. M oller/S. Timpf { 27 { FuGoe WS 10/11 Ein geeigneter Datentyp ist, analog zum allgemeinen Baumtyp, data Ord a => Heap a b = Empty | Node a b [Heap a b] Dabei ist a der Typ der Shlussel und b derjenige der Werte, die durh die Shlussel vertreten werden. B. M oller/S. Timpf { 28 { FuGoe WS 10/11 merge :: Ord a => Heap a b -> Heap a b -> Heap a b merge h Empty = h Die zugehorigen Operationen sind die folgenden: merge Empty h = h merge h@(Node key1 val1 hs) h’@(Node key2 val2 hs’) empty :: Ord a => Heap a b | key1<key2 = Node key1 val1 (h’:hs) empty = Empty | otherwise = Node key2 val2 (h:hs’) isEmpty :: Ord a => Heap a b -> Bool isEmpty Empty = True mergeAll:: Ord a => [Heap a b] -> Heap a b isEmpty _ mergeAll [] = Empty mergeAll [h] = h = False mergeAll (h:h’:hs) = merge (merge h h’) (mergeAll hs) unit :: Ord a => a -> b -> Heap a b unit key val = Node key val [] insert :: Ord a => (a, b) -> Heap a b -> Heap a b insert (key, val) h = merge (unit key val) h B. M oller/S. Timpf { 29 { FuGoe WS 10/11 findMin :: Ord a => Heap a b -> (a, b) findMin Empty = error "Heap.findMin: empty heap" B. M oller/S. Timpf { 30 { FuGoe WS 10/11 Mit diesen Operationen lasst sih Haldensortieren so implementieren (Shlussel und Wert sind hier jeweils gleih): build :: Ord a => [(a,b)] -> Heap a b findMin (Node key val _) = (key, val) build = foldr insert Empty deleteMin :: Ord a => Heap a b -> Heap a b deleteMin Empty toList :: Ord a => Heap a b -> [(a,b)] = Empty toList Empty = [] deleteMin (Node _ _ hs) = mergeAll hs toList h = x:toList r where (x,r) = (findMin h,deleteMin h) splitMin :: Ord a => Heap a b -> (a,b,Heap a b) splitMin Empty = error "Heap.splitMin: empty heap" splitMin (Node key val hs) = (key,val,mergeAll hs) heapsort :: Ord a => [a] -> [a] heapsort = (map fst) . toList . build . map (\x->(x,x)) B. M oller/S. Timpf { 31 { FuGoe WS 10/11 B. M oller/S. Timpf { 32 { FuGoe WS 10/11 Implementierung von Dijkstras Algorithmus: • Die klassishe imperative Implementierung konstruiert inkremen- Weiteres Hilfsmittel: invertierte Baume (vgl. Union-Find), dargestellt als Mengen von Pfaden von Baumknoten zur Wurzel type RTree = [Path] type LRTree a = [LPath a] tell ein Feld pre, das zu jedem Knoten x den Vorganger auf einem kurzesten Weg vom Startknoten s zu x enthalt. • Tatsahlih reprasentiert pre einen Spannbaum der Zusammenhangskomponente von s. • Dieser wird hier in der oben erwahnten Weise als Menge (bzw. Liste) von Pfaden dargestellt und statt des Feldes inkrementell mitberehnet. • Die Pfade werden eÆzient in einer mishbaren Halde verwaltet. • Ihre Knoteneintrage sind Paare, bestehend jeweils aus einem Pfad und der zugehorigen Lange. • Anders als im imperativen Fall werden einfah alle Pfade in die Halde eingetragen und die mit minimaler Lange durh die Haldenoperationen herausgesuht. B. M oller/S. Timpf { 33 { FuGoe WS 10/11 B. M oller/S. Timpf FuGoe WS 10/11 { 34 { dijkstra :: (Graph gr, Real b) => Heap b (LPath b) -> gr a b -> LRTree b dijkstra h g = Das wird durh die folgenden Funktionen realisiert: if isEmpty h || isEmpty g then [] spTree :: (Graph gr, Real b) => else let (_,p,h’) = splitMin h Node -> gr a b -> LRTree b -- hole Pfad minimaler Länge spTree s g = dijkstra (unit 0 [(s,0)]) g (v,d) -- Anfangshalde enthält nur die einelementige Halde = head p in case match v g of -- mit der Wurzel s (Just c,g’) -> p : dijkstra h’’ g’ where h’’ = mergeAll (h’ : expand d p c) (Nothing,g’) -> dijkstra h’ g’ B. M oller/S. Timpf { 35 { FuGoe WS 10/11 B. M oller/S. Timpf { 36 { FuGoe WS 10/11 Nun konnen wir die eigentlih interessierenden Funktionen programmieren: expand :: Real b => b -> LPath b -> Context a b -> [Heap b (LPath b)] expand d p (_,x,_,succlist) = map adaptDist succlist where adaptDist (e,v) = unit (e+d) ((v,e+d):p) -- e Kantengewicht einer von v ausgehenden Kante spLength :: (Graph gr, Real b) => Node -> Node -> gr a b -> b spLength s t g = getDistance t (spTree s g) • Alle Knoten in sulist sind Nahfolger von x. sp :: (Graph gr, Real b) => • Der Startknoten s ist von x auf dem Pfad p der Lange d erreihbar. sp s t g Node -> Node -> gr a b -> Path • Ist also v ein Nahfolger von x auf einer Kante der Lange l, so ist s von v aus auf dem um v verlangerten Pfad der Lange l+d erreihbar. B. M oller/S. Timpf { 37 { FuGoe WS 10/11 = getLPathNodes t (spTree s g) Dabei setzen die Funktionen getDistance und getLPathNodes voraus, dass die mit dem Knoten t beginnenden Pfade im ihrem zweiten Argument durh die Haldenstruktur nah ihrer Lange sortiert auftreten. B. M oller/S. Timpf { 38 { FuGoe WS 10/11 getDistance :: Node -> LRTree a -> a getDistance v pp = snd (head (findP v pp)) -- Distanz zum Startknoten ist in jedem pp-Pfad vermerkt getLPath :: Node -> LRTree a -> LPath a findP :: Node -> LRTree a -> [LNode a] getLPath v pp -- liefert den ersten Pfad, der mit dem -- invertierten Pfad in gewöhnlichen umrechnen = reverse (findP v pp) -- übergebenen Knoten beginnt findP v pp = getLPathNodes :: Node -> LRTree a -> Path if pp == [] getLPathNodes v pp then [] = map fst (getLPath v) -- Distanzinformation wegwerfen else if head pp == [] || fst (head pp) /= v then findP v tail pp else head pp B. M oller/S. Timpf { 39 { FuGoe WS 10/11 B. M oller/S. Timpf { 40 { FuGoe WS 10/11