{-# OPTIONS_HADDOCK hide #-}
module Data.GraphViz.Attributes.Same
       ( SameAttr
       , SAttrs
       , toSAttr
       , unSame
       , unSameSet
       ) where
import Data.GraphViz.Attributes.Complete(Attribute, Attributes, sameAttribute)
import Data.Function(on)
import qualified Data.Set as Set
import Data.Set(Set)
newtype SameAttr = SA { getAttr :: Attribute }
                 deriving (Show, Read)
instance Eq SameAttr where
  (==) = sameAttribute `on` getAttr
instance Ord SameAttr where
  compare sa1 sa2
    | sa1 == sa2 = EQ
    | otherwise  = (compare `on` getAttr) sa1 sa2
type SAttrs = Set SameAttr
toSAttr :: Attributes -> SAttrs
toSAttr = Set.fromList . map SA
unSame :: SAttrs -> Attributes
unSame = map getAttr . Set.toList
unSameSet :: SAttrs -> Set Attribute
unSameSet = Set.mapMonotonic getAttr