module Data.Relation (
Relation
, size
, null
, empty
, fromList
, singleton
, union
, unions
, intersection
, insert
, delete
, lookupDom
, lookupRan
, memberDom
, memberRan
, member
, notMember
, restrictDom
, restrictRan
, withoutDom
, withoutRan
, toList
, dom
, ran
, converse
) where
import Control.Monad (MonadPlus, guard)
import Data.Functor (Functor ((<$)))
import Data.Map (Map)
import Data.Maybe (fromMaybe)
import Data.Relation.Internal (Relation (Relation))
import Data.Set (Set)
import Prelude hiding (null)
import qualified Data.Foldable as F
import qualified Data.Map as M
import qualified Data.Relation.Internal as R
import qualified Data.Relation.Internal.Set as S
import qualified Data.Set as S
size :: Relation a b -> Int
size r = M.foldr ((+) . S.size) 0 (R.domain r)
empty :: Relation a b
empty = Relation M.empty M.empty
fromList :: (Ord a, Ord b) => [(a, b)] -> Relation a b
fromList xs = Relation
{ R.domain = M.fromListWith S.union $ snd2Set xs
, R.range = M.fromListWith S.union $ flipAndSet xs
}
where snd2Set = map (\(x, y) -> (x, S.singleton y))
flipAndSet = map (\(x, y) -> (y, S.singleton x))
toList :: Relation a b -> [(a, b)]
toList r = concatMap (\(x, y) -> zip (repeat x) (S.toList y)) (M.toList . R.domain $ r)
singleton :: a -> b -> Relation a b
singleton x y = Relation
{ R.domain = M.singleton x (S.singleton y)
, R.range = M.singleton y (S.singleton x)
}
union :: (Ord a, Ord b) => Relation a b -> Relation a b -> Relation a b
union r s = Relation
{ R.domain = M.unionWith S.union (R.domain r) (R.domain s)
, R.range = M.unionWith S.union (R.range r) (R.range s)
}
unions :: (Ord a, Ord b) => [Relation a b] -> Relation a b
unions = F.foldl' union empty
intersection :: (Ord a, Ord b) => Relation a b -> Relation a b -> Relation a b
intersection r s = Relation
{ R.domain = doubleIntersect (R.domain r) (R.domain s)
, R.range = doubleIntersect (R.range r) (R.range s)
}
ensure :: MonadPlus m => (a -> Bool) -> a -> m a
ensure p x = x <$ guard (p x)
doubleIntersect :: (Ord k, Ord v) => Map k (Set v) -> Map k (Set v) -> Map k (Set v)
doubleIntersect = M.mergeWithKey
(\_ l r -> ensure (not . S.null) (S.intersection l r))
(const M.empty)
(const M.empty)
insert :: (Ord a, Ord b) => a -> b -> Relation a b -> Relation a b
insert x y r = Relation domain' range'
where domain' = M.insertWith S.union x (S.singleton y) (R.domain r)
range' = M.insertWith S.union y (S.singleton x) (R.range r)
delete :: (Ord a, Ord b) => a -> b -> Relation a b -> Relation a b
delete x y r = Relation
{ R.domain = domain'
, R.range = range'
}
where domain' = M.update (erase y) x (R.domain r)
range' = M.update (erase x) y (R.range r)
erase e s = if S.singleton e == s then Nothing else Just $ S.delete e s
lookupDom :: Ord a => a -> Relation a b -> Set b
lookupDom x r = fromMaybe S.empty $ M.lookup x (R.domain r)
lookupRan :: Ord b => b -> Relation a b -> Set a
lookupRan y r = fromMaybe S.empty $ M.lookup y (R.range r)
memberDom :: Ord a => a -> Relation a b -> Bool
memberDom x r = not . S.null $ lookupDom x r
memberRan :: Ord b => b -> Relation a b -> Bool
memberRan y r = not . S.null $ lookupRan y r
null :: Relation a b -> Bool
null r = M.null $ R.domain r
member :: (Ord a, Ord b) => a -> b -> Relation a b -> Bool
member x y r = S.member y (lookupDom x r)
notMember :: (Ord a, Ord b) => a -> b -> Relation a b -> Bool
notMember x y r = not $ member x y r
dom :: Relation a b -> Set a
dom r = M.keysSet (R.domain r)
ran :: Relation a b -> Set b
ran r = M.keysSet (R.range r)
converse :: Relation a b -> Relation b a
converse r = Relation
{ R.domain = range'
, R.range = domain'
}
where range' = R.range r
domain' = R.domain r
restrictDom :: (Ord a, Ord b) => S.Set a -> Relation a b -> Relation a b
restrictDom s r = Relation
{ R.domain = M.restrictKeys (R.domain r) s
, R.range = M.mapMaybe (S.justUnlessEmpty . S.intersection s) (R.range r)
}
restrictRan :: (Ord a, Ord b) => S.Set b -> Relation a b -> Relation a b
restrictRan s r = Relation
{ R.domain = M.mapMaybe (S.justUnlessEmpty . S.intersection s) (R.domain r)
, R.range = M.restrictKeys (R.range r) s
}
withoutDom :: (Ord a, Ord b) => S.Set a -> Relation a b -> Relation a b
withoutDom s r = Relation
{ R.domain = M.withoutKeys (R.domain r) s
, R.range = M.mapMaybe (S.justUnlessEmpty . flip S.difference s) (R.range r)
}
withoutRan :: (Ord a, Ord b) => S.Set b -> Relation a b -> Relation a b
withoutRan s r = Relation
{ R.domain = M.mapMaybe (S.justUnlessEmpty . flip S.difference s) (R.domain r)
, R.range = M.withoutKeys (R.range r) s
}