{-# Language QuasiQuotes #-}
module Main where
import Advent (format)
import Data.Graph.Inductive (UGr, reachable, noComponents, mkUGraph)
main :: IO ()
IO ()
main =
do [(Node, [Node])]
input <- [format|2017 12 (%u <-> %u&(, )%n)*|]
let g :: UGr
g = [(Node, [Node])] -> UGr
toGraph [(Node, [Node])]
input
Node -> IO ()
forall a. Show a => a -> IO ()
print ([Node] -> Node
forall a. [a] -> Node
forall (t :: * -> *) a. Foldable t => t a -> Node
length (Node -> UGr -> [Node]
forall (gr :: * -> * -> *) a b.
Graph gr =>
Node -> gr a b -> [Node]
reachable Node
0 UGr
g))
Node -> IO ()
forall a. Show a => a -> IO ()
print (UGr -> Node
forall (gr :: * -> * -> *) a b. Graph gr => gr a b -> Node
noComponents UGr
g)
toGraph :: [(Int,[Int])] -> UGr
toGraph :: [(Node, [Node])] -> UGr
toGraph [(Node, [Node])]
xs = [Node] -> [Edge] -> UGr
forall (gr :: * -> * -> *).
Graph gr =>
[Node] -> [Edge] -> gr () ()
mkUGraph ((Node, [Node]) -> Node
forall a b. (a, b) -> a
fst ((Node, [Node]) -> Node) -> [(Node, [Node])] -> [Node]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Node, [Node])]
xs) ((Node, [Node]) -> [Edge]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
forall (f :: * -> *) a. Applicative f => (Node, f a) -> f (Node, a)
sequenceA ((Node, [Node]) -> [Edge]) -> [(Node, [Node])] -> [Edge]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [(Node, [Node])]
xs)