-- | -- Module: Data.Reify.Graph -- Copyright: (c) 2009 Andy Gill -- License: BSD3 -- -- Maintainer: Andy Gill -- Stability: unstable -- Portability: ghc -- -- This is the shared definition of a 'Graph' in Data.Reify. {-# LANGUAGE FlexibleContexts, UndecidableInstances #-} module Data.Reify.Graph ( Graph(..), ) where import Data.Unique -- 'Graph' is a basic graph structure over nodes of the higher kind 'e', with a single root. data Graph e = Graph [(Unique,e Unique)] Unique -- | If 'e' is s Functor, and 'e' is 'Show'-able, then we can 'Show' a 'Graph'. instance (Functor e,Show (e Int)) => Show (Graph e) where show (Graph netlist start) = "let " ++ show [ (hashUnique u,fmap hashUnique e) | (u,e) <- netlist ] ++ " in " ++ show (hashUnique start)