diff --git a/Cabal-hooks/Cabal-hooks.cabal b/Cabal-hooks/Cabal-hooks.cabal index bb6b197cf03..1f50247651e 100644 --- a/Cabal-hooks/Cabal-hooks.cabal +++ b/Cabal-hooks/Cabal-hooks.cabal @@ -62,7 +62,6 @@ library ScopedTypeVariables StandaloneDeriving Trustworthy - TypeFamilies TypeOperators TypeSynonymInstances UndecidableInstances diff --git a/Cabal-syntax/Cabal-syntax.cabal b/Cabal-syntax/Cabal-syntax.cabal index 85137dc147c..18ebca6a390 100644 --- a/Cabal-syntax/Cabal-syntax.cabal +++ b/Cabal-syntax/Cabal-syntax.cabal @@ -226,7 +226,6 @@ library ScopedTypeVariables StandaloneDeriving Trustworthy - TypeFamilies TypeOperators TypeSynonymInstances UndecidableInstances diff --git a/Cabal-syntax/src/Distribution/Compat/Graph.hs b/Cabal-syntax/src/Distribution/Compat/Graph.hs index ea37af99a77..05f3c422a29 100644 --- a/Cabal-syntax/src/Distribution/Compat/Graph.hs +++ b/Cabal-syntax/src/Distribution/Compat/Graph.hs @@ -1,8 +1,8 @@ {-# LANGUAGE BangPatterns #-} {-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} -- | @@ -107,40 +107,40 @@ import qualified Distribution.Compat.Prelude as Prelude -- | A graph of nodes @a@. The nodes are expected to have instance -- of class 'IsNode'. -data Graph a = Graph - { graphMap :: !(Map (Key a) a) +data Graph keyA a = Graph + { graphMap :: !(Map keyA a) , -- Lazily cached graph representation graphForward :: G.Graph , graphAdjoint :: G.Graph , graphVertexToNode :: G.Vertex -> a - , graphKeyToVertex :: Key a -> Maybe G.Vertex - , graphBroken :: [(a, [Key a])] + , graphKeyToVertex :: keyA -> Maybe G.Vertex + , graphBroken :: [(a, [keyA])] } -- NB: Not a Functor! (or Traversable), because you need --- to restrict Key a ~ Key b. We provide our own mapping +-- to restrict keyA ~ Key b. We provide our own mapping -- functions. -- General strategy is most operations are deferred to the -- Map representation. -instance Show a => Show (Graph a) where +instance Show a => Show (Graph keyA a) where show = show . toList -instance (IsNode a, Read a, Show (Key a)) => Read (Graph a) where +instance (IsNode keyA a, Read a, Show keyA) => Read (Graph keyA a) where readsPrec d s = map (first fromDistinctList) (readsPrec d s) -instance (IsNode a, Binary a, Show (Key a)) => Binary (Graph a) where +instance (IsNode keyA a, Binary a, Show keyA) => Binary (Graph keyA a) where put x = put (toList x) get = fmap fromDistinctList get -instance Structured a => Structured (Graph a) where +instance (Structured a, Typeable keyA) => Structured (Graph keyA a) where structure p = Nominal (typeRep p) 0 "Graph" [structure (Proxy :: Proxy a)] -instance (Eq (Key a), Eq a) => Eq (Graph a) where +instance (Eq keyA, Eq a) => Eq (Graph keyA a) where g1 == g2 = graphMap g1 == graphMap g2 -instance Foldable.Foldable Graph where +instance Foldable.Foldable (Graph keyA) where elem x = Foldable.elem x . graphMap fold = Foldable.fold . graphMap foldl f z = Foldable.foldl f z . graphMap @@ -156,7 +156,7 @@ instance Foldable.Foldable Graph where sum = Foldable.sum . graphMap toList = Foldable.toList . graphMap -instance (NFData a, NFData (Key a)) => NFData (Graph a) where +instance (NFData a, NFData keyA) => NFData (Graph keyA a) where rnf Graph { graphMap = m @@ -173,13 +173,11 @@ instance (NFData a, NFData (Key a)) => NFData (Graph a) where -- graph nodes. A node of type @a@ is associated with some unique key of -- type @'Key' a@; given a node we can determine its key ('nodeKey') -- and the keys of its neighbors ('nodeNeighbors'). -class Ord (Key a) => IsNode a where - type Key a - nodeKey :: a -> Key a - nodeNeighbors :: a -> [Key a] +class Ord keyA => IsNode keyA a | a -> keyA where + nodeKey :: a -> keyA + nodeNeighbors :: a -> [keyA] -instance (IsNode a, IsNode b, Key a ~ Key b) => IsNode (Either a b) where - type Key (Either a b) = Key a +instance (IsNode key a, IsNode key b) => IsNode key (Either a b) where nodeKey (Left x) = nodeKey x nodeKey (Right x) = nodeKey x nodeNeighbors (Left x) = nodeNeighbors x @@ -196,50 +194,49 @@ nodeValue (N a _ _) = a instance Functor (Node k) where fmap f (N a k ks) = N (f a) k ks -instance Ord k => IsNode (Node k a) where - type Key (Node k a) = k +instance Ord k => IsNode k (Node k a) where nodeKey (N _ k _) = k nodeNeighbors (N _ _ ks) = ks -- TODO: Maybe introduce a typeclass for items which just --- keys (so, Key associated type, and nodeKey method). But +-- keys (so, keyAssociated type, and nodeKey method). But -- I didn't need it here, so I didn't introduce it. -- Query -- | /O(1)/. Is the graph empty? -null :: Graph a -> Bool +null :: Graph keyA a -> Bool null = Map.null . toMap -- | /O(1)/. The number of nodes in the graph. -size :: Graph a -> Int +size :: Graph keyA a -> Int size = Map.size . toMap -- | /O(log V)/. Check if the key is in the graph. -member :: IsNode a => Key a -> Graph a -> Bool +member :: IsNode keyA a => keyA -> Graph keyA a -> Bool member k g = Map.member k (toMap g) -- | /O(log V)/. Lookup the node at a key in the graph. -lookup :: IsNode a => Key a -> Graph a -> Maybe a +lookup :: IsNode keyA a => keyA -> Graph keyA a -> Maybe a lookup k g = Map.lookup k (toMap g) -- Construction -- | /O(1)/. The empty graph. -empty :: IsNode a => Graph a +empty :: IsNode keyA a => Graph keyA a empty = fromMap Map.empty -- | /O(log V)/. Insert a node into a graph. -insert :: IsNode a => a -> Graph a -> Graph a +insert :: IsNode keyA a => a -> Graph keyA a -> Graph keyA a insert !n g = fromMap (Map.insert (nodeKey n) n (toMap g)) -- | /O(log V)/. Delete the node at a key from the graph. -deleteKey :: IsNode a => Key a -> Graph a -> Graph a +deleteKey :: IsNode keyA a => keyA -> Graph keyA a -> Graph keyA a deleteKey k g = fromMap (Map.delete k (toMap g)) -- | /O(log V)/. Lookup and delete. This function returns the deleted -- value if it existed. -deleteLookup :: IsNode a => Key a -> Graph a -> (Maybe a, Graph a) +deleteLookup :: IsNode keyA a => keyA -> Graph keyA a -> (Maybe a, Graph keyA a) deleteLookup k g = let (r, m') = Map.updateLookupWithKey (\_ _ -> Nothing) k (toMap g) in (r, fromMap m') @@ -249,19 +246,19 @@ deleteLookup k g = -- | /O(V + V')/. Right-biased union, preferring entries -- from the second map when conflicts occur. -- @'nodeKey' x = 'nodeKey' (f x)@. -unionRight :: IsNode a => Graph a -> Graph a -> Graph a +unionRight :: IsNode keyA a => Graph keyA a -> Graph keyA a -> Graph keyA a unionRight g g' = fromMap (Map.union (toMap g') (toMap g)) -- | /O(V + V')/. Left-biased union, preferring entries from -- the first map when conflicts occur. -unionLeft :: IsNode a => Graph a -> Graph a -> Graph a +unionLeft :: IsNode keyA a => Graph keyA a -> Graph keyA a -> Graph keyA a unionLeft = flip unionRight -- Graph-like operations -- | /Ω(V + E)/. Compute the strongly connected components of a graph. -- Requires amortized construction of graph. -stronglyConnComp :: Graph a -> [SCC a] +stronglyConnComp :: Graph keyA a -> [SCC a] stronglyConnComp g = map decode forest where forest = G.scc (graphForward g) @@ -278,25 +275,25 @@ stronglyConnComp g = map decode forest -- | /Ω(V + E)/. Compute the cycles of a graph. -- Requires amortized construction of graph. -cycles :: Graph a -> [[a]] +cycles :: Graph keyA a -> [[a]] cycles g = [vs | CyclicSCC vs <- stronglyConnComp g] -- | /O(1)/. Return a list of nodes paired with their broken -- neighbors (i.e., neighbor keys which are not in the graph). -- Requires amortized construction of graph. -broken :: Graph a -> [(a, [Key a])] +broken :: Graph keyA a -> [(a, [keyA])] broken g = graphBroken g -- | Lookup the immediate neighbors from a key in the graph. -- Requires amortized construction of graph. -neighbors :: Graph a -> Key a -> Maybe [a] +neighbors :: Graph keyA a -> keyA -> Maybe [a] neighbors g k = do v <- graphKeyToVertex g k return (map (graphVertexToNode g) (graphForward g ! v)) -- | Lookup the immediate reverse neighbors from a key in the graph. -- Requires amortized construction of graph. -revNeighbors :: Graph a -> Key a -> Maybe [a] +revNeighbors :: Graph keyA a -> keyA -> Maybe [a] revNeighbors g k = do v <- graphKeyToVertex g k return (map (graphVertexToNode g) (graphAdjoint g ! v)) @@ -305,7 +302,7 @@ revNeighbors g k = do -- Returns @Nothing@ if one (or more) keys are not present in -- the graph. -- Requires amortized construction of graph. -closure :: Graph a -> [Key a] -> Maybe [a] +closure :: Graph keyA a -> [keyA] -> Maybe [a] closure g ks = do vs <- traverse (graphKeyToVertex g) ks return (decodeVertexForest g (G.dfs (graphForward g) vs)) @@ -314,7 +311,7 @@ closure g ks = do -- of keys. Returns @Nothing@ if one (or more) keys are not present in -- the graph. -- Requires amortized construction of graph. -revClosure :: Graph a -> [Key a] -> Maybe [a] +revClosure :: Graph keyA a -> [keyA] -> Maybe [a] revClosure g ks = do vs <- traverse (graphKeyToVertex g) ks return (decodeVertexForest g (G.dfs (graphAdjoint g) vs)) @@ -322,17 +319,17 @@ revClosure g ks = do flattenForest :: Tree.Forest a -> [a] flattenForest = concatMap Tree.flatten -decodeVertexForest :: Graph a -> Tree.Forest G.Vertex -> [a] +decodeVertexForest :: Graph keyA a -> Tree.Forest G.Vertex -> [a] decodeVertexForest g = map (graphVertexToNode g) . flattenForest -- | Topologically sort the nodes of a graph. -- Requires amortized construction of graph. -topSort :: Graph a -> [a] +topSort :: Graph keyA a -> [a] topSort g = map (graphVertexToNode g) $ G.topSort (graphForward g) -- | Reverse topologically sort the nodes of a graph. -- Requires amortized construction of graph. -revTopSort :: Graph a -> [a] +revTopSort :: Graph keyA a -> [a] revTopSort g = map (graphVertexToNode g) $ G.topSort (graphAdjoint g) -- Conversions @@ -343,7 +340,7 @@ revTopSort g = map (graphVertexToNode g) $ G.topSort (graphAdjoint g) -- if you can't fulfill this invariant use @'fromList' ('Data.Map.elems' m)@ -- instead. The values of the map are assumed to already -- be in WHNF. -fromMap :: IsNode a => Map (Key a) a -> Graph a +fromMap :: IsNode keyA a => Map keyA a -> Graph keyA a fromMap m = Graph { graphMap = m @@ -377,7 +374,7 @@ fromMap m = bounds = (0, Map.size m - 1) -- | /O(V log V)/. Convert a list of nodes (with distinct keys) into a graph. -fromDistinctList :: (IsNode a, Show (Key a)) => [a] -> Graph a +fromDistinctList :: (IsNode keyA a, Show keyA) => [a] -> Graph keyA a fromDistinctList = fromMap . Map.fromListWith (\_ -> duplicateError) @@ -391,26 +388,26 @@ fromDistinctList = -- Map-like operations -- | /O(V)/. Convert a graph into a list of nodes. -toList :: Graph a -> [a] +toList :: Graph keyA a -> [a] toList g = Map.elems (toMap g) -- | /O(V)/. Convert a graph into a list of keys. -keys :: Graph a -> [Key a] +keys :: Graph keyA a -> [keyA] keys g = Map.keys (toMap g) -- | /O(V)/. Convert a graph into a set of keys. -keysSet :: Graph a -> Set.Set (Key a) +keysSet :: Graph keyA a -> Set.Set keyA keysSet g = Map.keysSet (toMap g) -- | /O(1)/. Convert a graph into a map from keys to nodes. -- The resulting map @m@ is guaranteed to have the property that -- @'Prelude.all' (\(k,n) -> k == 'nodeKey' n) ('Data.Map.toList' m)@. -toMap :: Graph a -> Map (Key a) a +toMap :: Graph keyA a -> Map keyA a toMap = graphMap -- Graph-like operations -- | /O(1)/. Convert a graph into a 'Data.Graph.Graph'. -- Requires amortized construction of graph. -toGraph :: Graph a -> (G.Graph, G.Vertex -> a, Key a -> Maybe G.Vertex) +toGraph :: Graph keyA a -> (G.Graph, G.Vertex -> a, keyA -> Maybe G.Vertex) toGraph g = (graphForward g, graphVertexToNode g, graphKeyToVertex g) diff --git a/Cabal-syntax/src/Distribution/Types/InstalledPackageInfo.hs b/Cabal-syntax/src/Distribution/Types/InstalledPackageInfo.hs index f57457d2e5b..d92c8aa14e1 100644 --- a/Cabal-syntax/src/Distribution/Types/InstalledPackageInfo.hs +++ b/Cabal-syntax/src/Distribution/Types/InstalledPackageInfo.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE TypeFamilies #-} module Distribution.Types.InstalledPackageInfo ( InstalledPackageInfo (..) @@ -113,8 +113,7 @@ instance Package.HasUnitId InstalledPackageInfo where instance Package.PackageInstalled InstalledPackageInfo where installedDepends = depends -instance IsNode InstalledPackageInfo where - type Key InstalledPackageInfo = UnitId +instance IsNode UnitId InstalledPackageInfo where nodeKey = installedUnitId nodeNeighbors = depends diff --git a/Cabal-syntax/src/Distribution/Utils/Path.hs b/Cabal-syntax/src/Distribution/Utils/Path.hs index a4d09334e01..64e7a0ee2c3 100644 --- a/Cabal-syntax/src/Distribution/Utils/Path.hs +++ b/Cabal-syntax/src/Distribution/Utils/Path.hs @@ -3,9 +3,10 @@ {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE KindSignatures #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE RoleAnnotations #-} -{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} diff --git a/Cabal-syntax/src/Distribution/Utils/Structured.hs b/Cabal-syntax/src/Distribution/Utils/Structured.hs index b88165a89bb..c035b1e67e8 100644 --- a/Cabal-syntax/src/Distribution/Utils/Structured.hs +++ b/Cabal-syntax/src/Distribution/Utils/Structured.hs @@ -2,10 +2,10 @@ {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} -{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} -- | diff --git a/Cabal-tests/tests/UnitTests/Distribution/Compat/Graph.hs b/Cabal-tests/tests/UnitTests/Distribution/Compat/Graph.hs index 0e2ea86318b..e4ebb225f0d 100644 --- a/Cabal-tests/tests/UnitTests/Distribution/Compat/Graph.hs +++ b/Cabal-tests/tests/UnitTests/Distribution/Compat/Graph.hs @@ -21,20 +21,20 @@ import Data.List (sort) tests :: [TestTree] tests = - [ testProperty "arbitrary unbroken" (prop_arbitrary_unbroken :: Graph (Node Int ()) -> Bool) - , testProperty "nodes consistent" (prop_nodes_consistent :: Graph (Node Int ()) -> Bool) - , testProperty "edges consistent" (prop_edges_consistent :: Graph (Node Int ()) -> Property) - , testProperty "closure consistent" (prop_closure_consistent :: Graph (Node Int ()) -> Property) + [ testProperty "arbitrary unbroken" (prop_arbitrary_unbroken :: Graph Int (Node Int ()) -> Bool) + , testProperty "nodes consistent" (prop_nodes_consistent :: Graph Int (Node Int ()) -> Bool) + , testProperty "edges consistent" (prop_edges_consistent :: Graph Int (Node Int ()) -> Property) + , testProperty "closure consistent" (prop_closure_consistent :: Graph Int (Node Int ()) -> Property) ] -- Our arbitrary instance does not generate broken graphs -prop_arbitrary_unbroken :: Graph a -> Bool +prop_arbitrary_unbroken :: Graph keyA a -> Bool prop_arbitrary_unbroken g = Prelude.null (broken g) -- Every node from 'toList' maps to a vertex which -- is present in the constructed graph, and maps back -- to a node correctly. -prop_nodes_consistent :: (Eq a, IsNode a) => Graph a -> Bool +prop_nodes_consistent :: (Eq a, IsNode keyA a) => Graph keyA a -> Bool prop_nodes_consistent g = all p (toList g) where (_, vtn, ktv) = toGraph g @@ -44,7 +44,7 @@ prop_nodes_consistent g = all p (toList g) -- A non-broken graph has the 'nodeNeighbors' of each node -- equal the recorded adjacent edges in the node graph. -prop_edges_consistent :: IsNode a => Graph a -> Property +prop_edges_consistent :: IsNode keyA a => Graph keyA a -> Property prop_edges_consistent g = Prelude.null (broken g) ==> all p (toList g) where (gr, vtn, ktv) = toGraph g @@ -52,7 +52,7 @@ prop_edges_consistent g = Prelude.null (broken g) ==> all p (toList g) == sort (map (nodeKey . vtn) (gr ! fromJust (ktv (nodeKey n)))) -- Closure is consistent with reachable -prop_closure_consistent :: (Show a, IsNode a) => Graph a -> Property +prop_closure_consistent :: (Show a, IsNode keyA a) => Graph keyA a -> Property prop_closure_consistent g = not (null g) ==> forAll (elements (toList g)) $ \n -> @@ -73,7 +73,7 @@ hasNoDups = loop Set.empty -- | Produces a graph of size @len@. We sample with 'suchThat'; if we -- dropped duplicate entries our size could be smaller. arbitraryGraph :: (Ord k, Show k, Arbitrary k, Arbitrary a) - => Int -> Gen (Graph (Node k a)) + => Int -> Gen (Graph k (Node k a)) arbitraryGraph len = do -- Careful! Assume k is much larger than size. ks <- vectorOf len arbitrary `suchThat` hasNoDups @@ -85,7 +85,7 @@ arbitraryGraph len = do return (fromDistinctList ns) instance (Ord k, Show k, Arbitrary k, Arbitrary a) - => Arbitrary (Graph (Node k a)) where + => Arbitrary (Graph k (Node k a)) where arbitrary = sized $ \n -> do len <- choose (0, n) arbitraryGraph len diff --git a/Cabal/Cabal.cabal b/Cabal/Cabal.cabal index 647cb5f1523..558361e4227 100644 --- a/Cabal/Cabal.cabal +++ b/Cabal/Cabal.cabal @@ -413,7 +413,6 @@ library ScopedTypeVariables StandaloneDeriving Trustworthy - TypeFamilies TypeOperators TypeSynonymInstances UndecidableInstances diff --git a/Cabal/src/Distribution/Backpack/ComponentsGraph.hs b/Cabal/src/Distribution/Backpack/ComponentsGraph.hs index aef3db817c6..5e8e1be66d5 100644 --- a/Cabal/src/Distribution/Backpack/ComponentsGraph.hs +++ b/Cabal/src/Distribution/Backpack/ComponentsGraph.hs @@ -30,7 +30,7 @@ import Text.PrettyPrint -- | A graph of source-level components by their source-level -- dependencies -type ComponentsGraph = Graph (Node ComponentName Component) +type ComponentsGraph = Graph ComponentName (Node ComponentName Component) -- | A list of components associated with the source level -- dependencies between them. diff --git a/Cabal/src/Distribution/Backpack/Configure.hs b/Cabal/src/Distribution/Backpack/Configure.hs index 55d1ae03254..dedc12f7e69 100644 --- a/Cabal/src/Distribution/Backpack/Configure.hs +++ b/Cabal/src/Distribution/Backpack/Configure.hs @@ -2,7 +2,6 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE NoMonoLocalBinds #-} -- | See @@ -232,12 +231,12 @@ toComponentLocalBuildInfos -- since we will pay for the ALL installed packages even if -- they are not related to what we are building. This was true -- in the old configure code. - external_graph :: Graph (Either InstalledPackageInfo ReadyComponent) + external_graph :: Graph UnitId (Either InstalledPackageInfo ReadyComponent) external_graph = Graph.fromDistinctList . map Left $ PackageIndex.allPackages installedPackageSet - internal_graph :: Graph (Either InstalledPackageInfo ReadyComponent) + internal_graph :: Graph UnitId (Either InstalledPackageInfo ReadyComponent) internal_graph = Graph.fromDistinctList . map Right diff --git a/Cabal/src/Distribution/Backpack/LinkedComponent.hs b/Cabal/src/Distribution/Backpack/LinkedComponent.hs index b2d2bc25066..782e5659bca 100644 --- a/Cabal/src/Distribution/Backpack/LinkedComponent.hs +++ b/Cabal/src/Distribution/Backpack/LinkedComponent.hs @@ -1,5 +1,4 @@ {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE TypeFamilies #-} -- | See module Distribution.Backpack.LinkedComponent diff --git a/Cabal/src/Distribution/Backpack/ReadyComponent.hs b/Cabal/src/Distribution/Backpack/ReadyComponent.hs index 3eef45fadbb..a87f456dfd0 100644 --- a/Cabal/src/Distribution/Backpack/ReadyComponent.hs +++ b/Cabal/src/Distribution/Backpack/ReadyComponent.hs @@ -1,6 +1,6 @@ +{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE TupleSections #-} -{-# LANGUAGE TypeFamilies #-} -- | See module Distribution.Backpack.ReadyComponent @@ -164,8 +164,7 @@ instance Package ReadyComponent where instance HasUnitId ReadyComponent where installedUnitId = rc_uid -instance IsNode ReadyComponent where - type Key ReadyComponent = UnitId +instance IsNode UnitId ReadyComponent where nodeKey = rc_uid nodeNeighbors rc = ( case rc_i rc of diff --git a/Cabal/src/Distribution/Types/ComponentLocalBuildInfo.hs b/Cabal/src/Distribution/Types/ComponentLocalBuildInfo.hs index 32f4aab473b..6eb88680479 100644 --- a/Cabal/src/Distribution/Types/ComponentLocalBuildInfo.hs +++ b/Cabal/src/Distribution/Types/ComponentLocalBuildInfo.hs @@ -1,5 +1,5 @@ {-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE MultiParamTypeClasses #-} module Distribution.Types.ComponentLocalBuildInfo ( ComponentLocalBuildInfo (..) @@ -114,8 +114,7 @@ data ComponentLocalBuildInfo instance Binary ComponentLocalBuildInfo instance Structured ComponentLocalBuildInfo -instance IsNode ComponentLocalBuildInfo where - type Key ComponentLocalBuildInfo = UnitId +instance IsNode UnitId ComponentLocalBuildInfo where nodeKey = componentUnitId nodeNeighbors = componentInternalDeps diff --git a/Cabal/src/Distribution/Types/LocalBuildConfig.hs b/Cabal/src/Distribution/Types/LocalBuildConfig.hs index 12648a8357b..dc1349bb28d 100644 --- a/Cabal/src/Distribution/Types/LocalBuildConfig.hs +++ b/Cabal/src/Distribution/Types/LocalBuildConfig.hs @@ -89,7 +89,7 @@ data PackageBuildDescr = PackageBuildDescr -- | Information about individual components in a package, -- determined after the configure step. data ComponentBuildDescr = ComponentBuildDescr - { componentGraph :: Graph ComponentLocalBuildInfo + { componentGraph :: Graph UnitId ComponentLocalBuildInfo -- ^ All the components to build, ordered by topological -- sort, and with their INTERNAL dependencies over the -- intrapackage dependency graph. diff --git a/Cabal/src/Distribution/Types/LocalBuildInfo.hs b/Cabal/src/Distribution/Types/LocalBuildInfo.hs index 854f454dc87..28008e3b8b4 100644 --- a/Cabal/src/Distribution/Types/LocalBuildInfo.hs +++ b/Cabal/src/Distribution/Types/LocalBuildInfo.hs @@ -158,7 +158,7 @@ pattern LocalBuildInfo -> Compiler -> Platform -> Maybe (SymbolicPath Pkg File) - -> Graph ComponentLocalBuildInfo + -> Graph UnitId ComponentLocalBuildInfo -> Map ComponentName [ComponentLocalBuildInfo] -> Map (PackageName, ComponentName) PromisedComponent -> InstalledPackageIndex diff --git a/Cabal/src/Distribution/Types/TargetInfo.hs b/Cabal/src/Distribution/Types/TargetInfo.hs index a743b0b21b0..7bb1b3e5071 100644 --- a/Cabal/src/Distribution/Types/TargetInfo.hs +++ b/Cabal/src/Distribution/Types/TargetInfo.hs @@ -1,5 +1,5 @@ {-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE MultiParamTypeClasses #-} module Distribution.Types.TargetInfo ( TargetInfo (..) @@ -33,7 +33,6 @@ data TargetInfo = TargetInfo instance Binary TargetInfo instance Structured TargetInfo -instance IsNode TargetInfo where - type Key TargetInfo = UnitId +instance IsNode UnitId TargetInfo where nodeKey = nodeKey . targetCLBI nodeNeighbors = nodeNeighbors . targetCLBI diff --git a/cabal-install-solver/src/Distribution/Solver/Modular/Cycles.hs b/cabal-install-solver/src/Distribution/Solver/Modular/Cycles.hs index b82e39a0d26..d537e2388fb 100644 --- a/cabal-install-solver/src/Distribution/Solver/Modular/Cycles.hs +++ b/cabal-install-solver/src/Distribution/Solver/Modular/Cycles.hs @@ -1,4 +1,5 @@ -{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE MultiParamTypeClasses #-} module Distribution.Solver.Modular.Cycles ( detectCyclesPhase ) where @@ -71,7 +72,7 @@ findCycles pkg rdm = -- strongly connected component. -- if hasCycle - then let scc :: G.Graph RevDepMapNode + then let scc :: G.Graph QPN RevDepMapNode scc = case G.cycles $ revDepMapToGraph rdm of [] -> findCyclesError "cannot find a strongly connected component" c : _ -> G.fromDistinctList c @@ -110,11 +111,10 @@ findCycles pkg rdm = data RevDepMapNode = RevDepMapNode QPN [(Component, QPN)] -instance G.IsNode RevDepMapNode where - type Key RevDepMapNode = QPN +instance G.IsNode QPN RevDepMapNode where nodeKey (RevDepMapNode qpn _) = qpn nodeNeighbors (RevDepMapNode _ ns) = ordNub $ map snd ns -revDepMapToGraph :: RevDepMap -> G.Graph RevDepMapNode +revDepMapToGraph :: RevDepMap -> G.Graph QPN RevDepMapNode revDepMapToGraph rdm = G.fromDistinctList [RevDepMapNode qpn ns | (qpn, ns) <- M.toList rdm] diff --git a/cabal-install-solver/src/Distribution/Solver/Types/ResolverPackage.hs b/cabal-install-solver/src/Distribution/Solver/Types/ResolverPackage.hs index 840e58aff94..44a9960877b 100644 --- a/cabal-install-solver/src/Distribution/Solver/Types/ResolverPackage.hs +++ b/cabal-install-solver/src/Distribution/Solver/Types/ResolverPackage.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE DeriveGeneric #-} module Distribution.Solver.Types.ResolverPackage ( ResolverPackage(..) @@ -42,8 +42,7 @@ resolverPackageExeDeps :: ResolverPackage loc -> CD.ComponentDeps [SolverId] resolverPackageExeDeps (PreExisting ipkg) = instSolverPkgExeDeps ipkg resolverPackageExeDeps (Configured spkg) = solverPkgExeDeps spkg -instance IsNode (ResolverPackage loc) where - type Key (ResolverPackage loc) = SolverId +instance IsNode SolverId (ResolverPackage loc) where nodeKey (PreExisting ipkg) = PreExistingId (packageId ipkg) (installedUnitId ipkg) nodeKey (Configured spkg) = PlannedId (packageId spkg) -- Use dependencies for ALL components diff --git a/cabal-install/src/Distribution/Client/Dependency.hs b/cabal-install/src/Distribution/Client/Dependency.hs index a65c41cb046..e18c855f53e 100644 --- a/cabal-install/src/Distribution/Client/Dependency.hs +++ b/cabal-install/src/Distribution/Client/Dependency.hs @@ -943,7 +943,7 @@ validateSolverResult platform comp indepGoals pkgs = Left problems -> error (formatPlanProblems problems) problems -> error (formatPkgProblems problems) where - graph :: Graph.Graph (ResolverPackage UnresolvedPkgLoc) + graph :: Graph.Graph SolverId (ResolverPackage UnresolvedPkgLoc) graph = Graph.fromDistinctList pkgs formatPkgProblems :: [PlanPackageProblem] -> String diff --git a/cabal-install/src/Distribution/Client/InstallPlan.hs b/cabal-install/src/Distribution/Client/InstallPlan.hs index 671617d2726..72c5146ec1b 100644 --- a/cabal-install/src/Distribution/Client/InstallPlan.hs +++ b/cabal-install/src/Distribution/Client/InstallPlan.hs @@ -2,12 +2,8 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE TypeFamilies #-} - ------------------------------------------------------------------------------ - ------------------------------------------------------------------------------ -- | -- Module : Distribution.Client.InstallPlan @@ -193,7 +189,7 @@ foldPlanPackage f _ (PreExisting ipkg) = f ipkg foldPlanPackage _ g (Configured srcpkg) = g srcpkg foldPlanPackage _ g (Installed srcpkg) = g srcpkg -type IsUnit a = (IsNode a, Key a ~ UnitId) +type IsUnit a = IsNode UnitId a depends :: IsUnit a => a -> [UnitId] depends = nodeNeighbors @@ -201,10 +197,9 @@ depends = nodeNeighbors -- NB: Expanded constraint synonym here to avoid undecidable -- instance errors in GHC 7.8 and earlier. instance - (IsNode ipkg, IsNode srcpkg, Key ipkg ~ UnitId, Key srcpkg ~ UnitId) - => IsNode (GenericPlanPackage ipkg srcpkg) + (IsNode UnitId ipkg, IsNode UnitId srcpkg) + => IsNode UnitId (GenericPlanPackage ipkg srcpkg) where - type Key (GenericPlanPackage ipkg srcpkg) = UnitId nodeKey (PreExisting ipkg) = nodeKey ipkg nodeKey (Configured spkg) = nodeKey spkg nodeKey (Installed spkg) = nodeKey spkg @@ -254,7 +249,7 @@ instance configuredId (Installed spkg) = configuredId spkg data GenericInstallPlan ipkg srcpkg = GenericInstallPlan - { planGraph :: !(Graph (GenericPlanPackage ipkg srcpkg)) + { planGraph :: !(Graph UnitId (GenericPlanPackage ipkg srcpkg)) , planIndepGoals :: !IndependentGoals } @@ -268,7 +263,7 @@ type InstallPlan = mkInstallPlan :: (IsUnit ipkg, IsUnit srcpkg) => String - -> Graph (GenericPlanPackage ipkg srcpkg) + -> Graph UnitId (GenericPlanPackage ipkg srcpkg) -> IndependentGoals -> GenericInstallPlan ipkg srcpkg mkInstallPlan loc graph indepGoals = @@ -297,10 +292,8 @@ instance (Structured ipkg, Structured srcpkg) => Structured (GenericInstallPlan ] instance - ( IsNode ipkg - , Key ipkg ~ UnitId - , IsNode srcpkg - , Key srcpkg ~ UnitId + ( IsNode UnitId ipkg + , IsNode UnitId srcpkg , Binary ipkg , Binary srcpkg ) @@ -365,13 +358,13 @@ showPlanPackageTag (Installed _) = "Installed" new :: (IsUnit ipkg, IsUnit srcpkg) => IndependentGoals - -> Graph (GenericPlanPackage ipkg srcpkg) + -> Graph UnitId (GenericPlanPackage ipkg srcpkg) -> GenericInstallPlan ipkg srcpkg new indepGoals graph = mkInstallPlan "new" graph indepGoals toGraph :: GenericInstallPlan ipkg srcpkg - -> Graph (GenericPlanPackage ipkg srcpkg) + -> Graph UnitId (GenericPlanPackage ipkg srcpkg) toGraph = planGraph toList @@ -1004,7 +997,7 @@ execute jobCtl keepGoing depFailure plan installPkg = valid :: (IsUnit ipkg, IsUnit srcpkg) => String - -> Graph (GenericPlanPackage ipkg srcpkg) + -> Graph UnitId (GenericPlanPackage ipkg srcpkg) -> Bool valid loc graph = case problems graph of @@ -1046,7 +1039,7 @@ showPlanProblem (PackageStateInvalid pkg pkg') = -- Use 'showPlanProblem' for a human readable explanation. problems :: (IsUnit ipkg, IsUnit srcpkg) - => Graph (GenericPlanPackage ipkg srcpkg) + => Graph UnitId (GenericPlanPackage ipkg srcpkg) -> [PlanProblem ipkg srcpkg] problems graph = [ PackageMissingDeps diff --git a/cabal-install/src/Distribution/Client/ProjectBuilding.hs b/cabal-install/src/Distribution/Client/ProjectBuilding.hs index 7bf6de869a5..cc69e804722 100644 --- a/cabal-install/src/Distribution/Client/ProjectBuilding.hs +++ b/cabal-install/src/Distribution/Client/ProjectBuilding.hs @@ -1,10 +1,10 @@ {-# LANGUAGE BangPatterns #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} +{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE NoMonoLocalBinds #-} module Distribution.Client.ProjectBuilding diff --git a/cabal-install/src/Distribution/Client/ProjectPlanOutput.hs b/cabal-install/src/Distribution/Client/ProjectPlanOutput.hs index 9ab68f58e8a..2867cca7559 100644 --- a/cabal-install/src/Distribution/Client/ProjectPlanOutput.hs +++ b/cabal-install/src/Distribution/Client/ProjectPlanOutput.hs @@ -509,7 +509,7 @@ data PostBuildProjectStatus = PostBuildProjectStatus -- or data file generation failing. -- -- This is a subset of 'packagesInvalidByChangedLibDeps'. - , packagesLibDepGraph :: Graph (Node UnitId ElaboratedPlanPackage) + , packagesLibDepGraph :: Graph UnitId (Node UnitId ElaboratedPlanPackage) -- ^ A subset of the plan graph, including only dependency-on-library -- edges. That is, dependencies /on/ libraries, not dependencies /of/ -- libraries. This tells us all the libraries that packages link to. @@ -629,7 +629,7 @@ postBuildProjectStatus ) -- The plan graph but only counting dependency-on-library edges - packagesLibDepGraph :: Graph (Node UnitId ElaboratedPlanPackage) + packagesLibDepGraph :: Graph UnitId (Node UnitId ElaboratedPlanPackage) packagesLibDepGraph = Graph.fromDistinctList [ Graph.N pkg (installedUnitId pkg) libdeps diff --git a/cabal-install/src/Distribution/Client/ProjectPlanning.hs b/cabal-install/src/Distribution/Client/ProjectPlanning.hs index 685e46dfa77..c6e6f7793f6 100644 --- a/cabal-install/src/Distribution/Client/ProjectPlanning.hs +++ b/cabal-install/src/Distribution/Client/ProjectPlanning.hs @@ -1,10 +1,10 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE TypeFamilies #-} -- | -- /Elaborated: worked out with great care and nicety of detail; executed with great minuteness: elaborate preparations; elaborate care./ @@ -3380,8 +3380,7 @@ instance Package PrunedPackage where instance HasUnitId PrunedPackage where installedUnitId = Graph.nodeKey -instance Graph.IsNode PrunedPackage where - type Key PrunedPackage = UnitId +instance Graph.IsNode UnitId PrunedPackage where nodeKey (PrunedPackage elab _) = Graph.nodeKey elab nodeNeighbors (PrunedPackage _ deps) = deps @@ -3472,7 +3471,7 @@ pruneInstallPlanPass1 pkgs pruned_packages :: [ElaboratedPlanPackage] pruned_packages = map (mapConfiguredPackage fromPrunedPackage) (fromMaybe [] $ Graph.closure graph roots) - closed_graph :: Graph.Graph ElaboratedPlanPackage + closed_graph :: Graph.Graph UnitId ElaboratedPlanPackage closed_graph = Graph.fromDistinctList pruned_packages -- whether any package has repl targets enabled, and we need to use multi-repl. @@ -3828,10 +3827,10 @@ pruneInstallPlanToDependencies pkgTargets installPlan = -- if the remaining graph is broken or not, ie any packages with dangling -- dependencies. If there are then we cannot prune the given targets. checkBrokenDeps - :: Graph.Graph ElaboratedPlanPackage + :: Graph.Graph UnitId ElaboratedPlanPackage -> Either CannotPruneDependencies - (Graph.Graph ElaboratedPlanPackage) + (Graph.Graph UnitId ElaboratedPlanPackage) checkBrokenDeps graph = case Graph.broken graph of [] -> Right graph diff --git a/cabal-install/src/Distribution/Client/ProjectPlanning/SetupPolicy.hs b/cabal-install/src/Distribution/Client/ProjectPlanning/SetupPolicy.hs index a510ea2bff6..6dbfcd865bc 100644 --- a/cabal-install/src/Distribution/Client/ProjectPlanning/SetupPolicy.hs +++ b/cabal-install/src/Distribution/Client/ProjectPlanning/SetupPolicy.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE MultiParamTypeClasses #-} -- | Setup.hs script policy -- @@ -170,9 +170,7 @@ instance Package NonSetupLibDepSolverPlanPackage where packageId (NonSetupLibDepSolverPlanPackage spkg) = packageId spkg -instance IsNode NonSetupLibDepSolverPlanPackage where - type Key NonSetupLibDepSolverPlanPackage = SolverId - +instance IsNode SolverId NonSetupLibDepSolverPlanPackage where nodeKey (NonSetupLibDepSolverPlanPackage spkg) = nodeKey spkg @@ -190,7 +188,7 @@ instance IsNode NonSetupLibDepSolverPlanPackage where packageSetupScriptSpecVersion :: SetupScriptStyle -> PackageDescription - -> Graph.Graph NonSetupLibDepSolverPlanPackage + -> Graph.Graph SolverId NonSetupLibDepSolverPlanPackage -> ComponentDeps [SolverId] -> Version -- We're going to be using the internal Cabal library, so the spec version of diff --git a/cabal-install/src/Distribution/Client/ProjectPlanning/Types.hs b/cabal-install/src/Distribution/Client/ProjectPlanning/Types.hs index 6aa1065d20e..3af8dd9934c 100644 --- a/cabal-install/src/Distribution/Client/ProjectPlanning/Types.hs +++ b/cabal-install/src/Distribution/Client/ProjectPlanning/Types.hs @@ -2,8 +2,8 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NamedFieldPuns #-} -{-# LANGUAGE TypeFamilies #-} -- | Types used while planning how to build everything in a project. -- @@ -493,8 +493,7 @@ instance HasConfiguredId ElaboratedConfiguredPackage where instance HasUnitId ElaboratedConfiguredPackage where installedUnitId = elabUnitId -instance IsNode ElaboratedConfiguredPackage where - type Key ElaboratedConfiguredPackage = UnitId +instance IsNode UnitId ElaboratedConfiguredPackage where nodeKey = elabUnitId nodeNeighbors = elabOrderDependencies diff --git a/cabal-install/src/Distribution/Client/SolverInstallPlan.hs b/cabal-install/src/Distribution/Client/SolverInstallPlan.hs index c0f1ff4dd2c..8f0dd18f835 100644 --- a/cabal-install/src/Distribution/Client/SolverInstallPlan.hs +++ b/cabal-install/src/Distribution/Client/SolverInstallPlan.hs @@ -1,9 +1,4 @@ {-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE TypeFamilies #-} - ------------------------------------------------------------------------------ - ------------------------------------------------------------------------------ -- | -- Module : Distribution.Client.SolverInstallPlan @@ -86,7 +81,7 @@ import qualified Distribution.Compat.Graph as Graph type SolverPlanPackage = ResolverPackage UnresolvedPkgLoc -type SolverPlanIndex = Graph SolverPlanPackage +type SolverPlanIndex = Graph SolverId SolverPlanPackage data SolverInstallPlan = SolverInstallPlan { planIndex :: !SolverPlanIndex @@ -301,7 +296,7 @@ nonSetupClosure -> SolverPlanIndex nonSetupClosure index pkgids0 = closure Graph.empty pkgids0 where - closure :: Graph SolverPlanPackage -> [SolverId] -> SolverPlanIndex + closure :: Graph SolverId SolverPlanPackage -> [SolverId] -> SolverPlanIndex closure completed [] = completed closure completed (pkgid : pkgids) = case Graph.lookup pkgid index of diff --git a/cabal-install/src/Distribution/Client/Types.hs b/cabal-install/src/Distribution/Client/Types.hs index 841a4dbc9d2..4ff9d84daa4 100644 --- a/cabal-install/src/Distribution/Client/Types.hs +++ b/cabal-install/src/Distribution/Client/Types.hs @@ -1,9 +1,3 @@ -{-# LANGUAGE TypeFamilies #-} - ------------------------------------------------------------------------------ - ------------------------------------------------------------------------------ - -- | -- Module : Distribution.Client.Types -- Copyright : (c) David Himmelstrup 2005 diff --git a/cabal-install/src/Distribution/Client/Types/ConfiguredPackage.hs b/cabal-install/src/Distribution/Client/Types/ConfiguredPackage.hs index 0b7d62e7e77..f051ef22c94 100644 --- a/cabal-install/src/Distribution/Client/Types/ConfiguredPackage.hs +++ b/cabal-install/src/Distribution/Client/Types/ConfiguredPackage.hs @@ -1,5 +1,5 @@ {-# LANGUAGE DeriveGeneric #-} -{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE MultiParamTypeClasses #-} module Distribution.Client.Types.ConfiguredPackage ( ConfiguredPackage (..) @@ -58,8 +58,7 @@ instance HasConfiguredId (ConfiguredPackage loc) where instance PackageFixedDeps (ConfiguredPackage loc) where depends = fmap (map (newSimpleUnitId . confInstId)) . confPkgDeps -instance IsNode (ConfiguredPackage loc) where - type Key (ConfiguredPackage loc) = UnitId +instance IsNode UnitId (ConfiguredPackage loc) where nodeKey = newSimpleUnitId . confPkgId -- TODO: if we update ConfiguredPackage to support order-only diff --git a/cabal-install/src/Distribution/Client/Types/ReadyPackage.hs b/cabal-install/src/Distribution/Client/Types/ReadyPackage.hs index e04b5af79c8..256d898b198 100644 --- a/cabal-install/src/Distribution/Client/Types/ReadyPackage.hs +++ b/cabal-install/src/Distribution/Client/Types/ReadyPackage.hs @@ -1,6 +1,8 @@ {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} -{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE UndecidableInstances #-} module Distribution.Client.Types.ReadyPackage ( GenericReadyPackage (..) @@ -33,8 +35,7 @@ newtype GenericReadyPackage srcpkg = ReadyPackage srcpkg -- see 'ConfiguredPacka ) -- Can't newtype derive this -instance IsNode srcpkg => IsNode (GenericReadyPackage srcpkg) where - type Key (GenericReadyPackage srcpkg) = Key srcpkg +instance IsNode key srcpkg => IsNode key (GenericReadyPackage srcpkg) where nodeKey (ReadyPackage spkg) = nodeKey spkg nodeNeighbors (ReadyPackage spkg) = nodeNeighbors spkg diff --git a/cabal-install/tests/UnitTests/Distribution/Client/InstallPlan.hs b/cabal-install/tests/UnitTests/Distribution/Client/InstallPlan.hs index 9db7109fbc6..3a783d3145b 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/InstallPlan.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/InstallPlan.hs @@ -1,5 +1,6 @@ {-# LANGUAGE ConstraintKinds #-} -{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NoMonoLocalBinds #-} module UnitTests.Distribution.Client.InstallPlan (tests) where @@ -169,8 +170,7 @@ instance Show TestInstallPlan where data TestPkg = TestPkg PackageId UnitId [UnitId] deriving (Eq, Show) -instance IsNode TestPkg where - type Key TestPkg = UnitId +instance IsNode UnitId TestPkg where nodeKey (TestPkg _ ipkgid _) = ipkgid nodeNeighbors (TestPkg _ _ deps) = deps